|
From: Andy S. <And...@co...> - 2010-09-07 11:05:25
|
diffing dir...
Tue Sep 7 06:58:30 EDT 2010 Andy Stewart <laz...@gm...>
* Add new module ModelView.CellRendererAccel
Ignore-this: ce17e043407179936e4d279aa1101d0
{
hunk ./gtk/Graphics/UI/Gtk.chs 118
+ module Graphics.UI.Gtk.ModelView.CellRendererAccel,
hunk ./gtk/Graphics/UI/Gtk.chs 329
+import Graphics.UI.Gtk.ModelView.CellRendererAccel
addfile ./gtk/Graphics/UI/Gtk/ModelView/CellRendererAccel.chs
hunk ./gtk/Graphics/UI/Gtk/ModelView/CellRendererAccel.chs 1
+{-# LANGUAGE CPP #-}
+-- -*-haskell-*-
+-- GIMP Toolkit (GTK) Widget CellRendererAccel
+--
+-- Author : Andy Stewart
+--
+-- Created: 25 Mar 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)
+--
+-- Renders a keyboard accelerator in a cell
+--
+-- * Module available since Gtk+ version 2.10
+--
+module Graphics.UI.Gtk.ModelView.CellRendererAccel (
+
+-- * Detail
+--
+-- | 'CellRendererAccel' displays a keyboard accelerator (i.e. a key
+-- combination like \<Control>-a). If the cell renderer is editable, the
+-- accelerator can be changed by simply typing the new combination.
+--
+-- The 'CellRendererAccel' cell renderer was added in Gtk+ 2.10.
+
+-- * Class Hierarchy
+--
+-- |
+-- @
+-- | 'GObject'
+-- | +----'Object'
+-- | +----'CellRenderer'
+-- | +----'CellRendererText'
+-- | +----CellRendererAccel
+-- @
+
+#if GTK_CHECK_VERSION(2,10,0)
+-- * Types
+ CellRendererAccel,
+ CellRendererAccelClass,
+ castToCellRendererAccel,
+ toCellRendererAccel,
+
+-- * Enums
+ CellRendererAccelMode(..),
+
+-- * Constructors
+ cellRendererAccelNew,
+
+-- * Attributes
+ cellRendererAccelAccelKey,
+ cellRendererAccelAccelMods,
+ cellRendererAccelKeycode,
+ cellRendererAccelAccelMode,
+
+-- * Signals
+ accelEdited,
+ accelCleared,
+#endif
+ ) where
+
+import Control.Monad (liftM)
+
+import System.Glib.FFI
+import System.Glib.Attributes
+import System.Glib.Properties
+import Graphics.UI.Gtk.Gdk.Enums (Modifier)
+import Graphics.UI.Gtk.Abstract.Object (makeNewObject)
+{#import Graphics.UI.Gtk.Signals#}
+{#import Graphics.UI.Gtk.Types#}
+
+{# context lib="gtk" prefix="gtk" #}
+
+#if GTK_CHECK_VERSION(2,10,0)
+--------------------
+-- Enums
+{#enum CellRendererAccelMode {underscoreToCase} deriving (Bounded,Eq,Show)#}
+
+--------------------
+-- Constructors
+
+-- | Creates a new 'CellRendererAccel'.
+--
+-- * Available since Gtk+ version 2.10
+--
+cellRendererAccelNew :: IO CellRendererAccel
+cellRendererAccelNew =
+ makeNewObject mkCellRendererAccel $ liftM castPtr $
+ {# call gtk_cell_renderer_accel_new #}
+
+--------------------
+-- Attributes
+
+-- | The keyval of the accelerator.
+-- [_$_]
+-- Allowed values: <= GMaxint
+-- [_$_]
+-- Default value: 0
+--
+-- * Available since Gtk+ version 2.10
+--
+cellRendererAccelAccelKey :: CellRendererAccelClass self => Attr self Int
+cellRendererAccelAccelKey = newAttrFromUIntProperty "accel-key"
+
+-- | The modifier mask of the accelerator.
+--
+-- * Available since Gtk+ version 2.10
+--
+cellRendererAccelAccelMods :: CellRendererAccelClass self => Attr self [Modifier]
+cellRendererAccelAccelMods = newAttrFromFlagsProperty "accel-mods"
+ {# call pure unsafe gdk_modifier_type_get_type #}
+
+-- | The hardware keycode of the accelerator. Note that the hardware keycode is only relevant if the key
+-- does not have a keyval. Normally, the keyboard configuration should assign keyvals to all keys.
+-- [_$_]
+-- Allowed values: <= GMaxint
+-- [_$_]
+-- Default value: 0
+--
+-- * Available since Gtk+ version 2.10
+--
+cellRendererAccelKeycode :: CellRendererAccelClass self => Attr self Int
+cellRendererAccelKeycode = newAttrFromUIntProperty "keycode"
+
+-- | Determines if the edited accelerators are GTK+ accelerators. If they are, consumed modifiers are
+-- suppressed, only accelerators accepted by GTK+ are allowed, and the accelerators are rendered in the
+-- same way as they are in menus.
+-- [_$_]
+-- Default value: 'CellRendererAccelModeGtk'
+--
+-- * Available since Gtk+ version 2.10
+--
+cellRendererAccelAccelMode :: CellRendererAccelClass self => Attr self CellRendererAccelMode
+cellRendererAccelAccelMode = newAttrFromEnumProperty "accel-mode"
+ {# call pure unsafe gtk_cell_renderer_accel_mode_get_type #}
+
+--------------------
+-- Signals
+
+-- | Gets emitted when the user has selected a new accelerator.
+--
+-- * Available since Gtk+ version 2.10
+--
+accelEdited :: CellRendererAccelClass self => Signal self (String -> Int -> Modifier -> Int -> IO ())
+accelEdited = Signal (connect_STRING_INT_ENUM_INT__NONE "accel_edited")
+
+-- | Gets emitted when the user has removed the accelerator.
+--
+-- * Available since Gtk+ version 2.10
+--
+accelCleared :: CellRendererAccelClass self => Signal self (String -> IO ())
+accelCleared = Signal (connect_STRING__NONE "accel_cleared")
+#endif
hunk ./gtk/gtk.cabal 260
+ Graphics.UI.Gtk.ModelView.CellRendererAccel
hunk ./gtk/hierarchy.list 189
+ GtkCellRendererAccel if gtk-2.10
hunk ./gtk/marshal.list 160
+# For CellRendererAccel
+NONE:STRING,INT,ENUM,INT
+
}
|