diffing dir...
Fri Oct 22 16:46:15 EDT 2010 Andy Stewart <laz...@gm...>
* New module in GTK+2.22 : GtkAccessible
Ignore-this: d31c2b7c9e1fe0cb09c5c134fa8c88a8
{
hunk ./gtk/Graphics/UI/Gtk.chs 229
+ module Graphics.UI.Gtk.Misc.Accessible,
hunk ./gtk/Graphics/UI/Gtk.chs 464
+import Graphics.UI.Gtk.Misc.Accessible
addfile ./gtk/Graphics/UI/Gtk/Misc/Accessible.chs
hunk ./gtk/Graphics/UI/Gtk/Misc/Accessible.chs 1
+{-# LANGUAGE CPP #-}
+-- -*-haskell-*-
+-- GIMP Toolkit (GTK) Widget accessible
+--
+-- Author : Andy Stewart
+--
+-- Created: 23 Oct 2010
+--
+-- Copyright (C) 2010 Andy Stewart
+--
+-- This library is free software; you can redistribute it and/or
+-- modify it under the terms of the GNU Lesser General Public
+-- License as published by the Free Software Foundation; either
+-- version 2.1 of the License, or (at your option) any later version.
+--
+-- This library is distributed in the hope that it will be useful,
+-- but WITHOUT ANY WARRANTY; without even the implied warranty of
+-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
+-- Lesser General Public License for more details.
+--
+-- |
+-- Maintainer : gtk...@li...
+-- Stability : provisional
+-- Portability : portable (depends on GHC)
+--
+-- A 'Object' representing an adjustable bounded value
+--
+module Graphics.UI.Gtk.Misc.Accessible (
+-- * Detail
+--
+-- | Accessible accessibility support for widgets.
+-- [_$_]
hunk ./gtk/Graphics/UI/Gtk/Misc/Accessible.chs 34
+-- * Class Hierarchy
+-- |
+-- @
+-- | 'GObject'
+-- | +----'AtkObject'
+-- | +----Accessible
+-- @
+
+#if GTK_CHECK_VERSION(2,22,0)
+-- * Types
+ Accessible,
+ AccessibleClass,
+ castToAccessible, gTypeAccessible,
+ toAccessible,
+
+-- * Methods
+ accessibleGetWidget,
+ accessibleSetWidget
+#endif
+) where
+
+import Control.Monad (liftM)
+
+import System.Glib.FFI
+import System.Glib.Attributes
+import System.Glib.Properties
+import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
+{#import Graphics.UI.Gtk.Types#}
+{#import Graphics.UI.Gtk.Signals#}
+
+{# context lib="gtk" prefix="gtk" #}
+
+#if GTK_CHECK_VERSION(2,22,0)
+--------------------
+-- Methods
+
+-- | Gets the 'Widget' corresponding to the 'Accessible'.
+--
+-- * Available since Gtk+ version 2.22
+--
+accessibleGetWidget :: AccessibleClass self => self
+ -> IO (Maybe Widget) -- ^ returns the 'Widget' corresponding to the 'Accessible', or 'Nothing'.
+accessibleGetWidget self =
+ maybeNull (makeNewObject mkWidget) $
+ {# call accessible_get_widget #}
+ (toAccessible self)
+
+-- | Sets the 'Widget' corresponding to the 'Accessible'.
+--
+-- * Available since Gtk+ version 2.22
+--
+accessibleSetWidget :: (AccessibleClass self, WidgetClass widget) [_$_]
+ => self -- ^ @accessible@ a 'Accessible' [_$_]
+ -> widget -- ^ @widget@ a 'Widget' [_$_]
+ -> IO ()
+accessibleSetWidget self widget = [_$_]
+ {#call accessible_set_widget #}
+ (toAccessible self)
+ (toWidget widget)
+#endif
hunk ./gtk/gtk.cabal 249
+ Graphics.UI.Gtk.Misc.Accessible
hunk ./gtk/hierarchy.list 25
+ AtkObject
+ GtkAccessible if gtk-2.22
}
|