| Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte | 
|---|---|
| License | LGPL-2.1 | 
| Maintainer | Iñaki García Etxebarria | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
GI.Gtk.Objects.AccelGroup
Description
A AccelGroup represents a group of keyboard accelerators,
 typically attached to a toplevel Window (with
 windowAddAccelGroup). Usually you won’t need to create a
 AccelGroup directly; instead, when using UIManager, GTK+
 automatically sets up the accelerators for your menus in the ui
 manager’s AccelGroup.
Note that “accelerators” are different from
 “mnemonics”. Accelerators are shortcuts for
 activating a menu item; they appear alongside the menu item they’re a
 shortcut for. For example “Ctrl+Q” might appear alongside the “Quit”
 menu item. Mnemonics are shortcuts for GUI elements such as text
 entries or buttons; they appear as underlined characters. See
 labelNewWithMnemonic. Menu items can have both accelerators
 and mnemonics, of course.
Synopsis
- newtype AccelGroup = AccelGroup (ManagedPtr AccelGroup)
 - class (GObject o, IsDescendantOf AccelGroup o) => IsAccelGroup o
 - toAccelGroup :: (MonadIO m, IsAccelGroup o) => o -> m AccelGroup
 - accelGroupActivate :: (HasCallStack, MonadIO m, IsAccelGroup a, IsObject b) => a -> Word32 -> b -> Word32 -> [ModifierType] -> m Bool
 - accelGroupConnect :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> Word32 -> [ModifierType] -> [AccelFlags] -> GClosure C_AccelGroupActivate -> m ()
 - accelGroupConnectByPath :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> Text -> GClosure b -> m ()
 - accelGroupDisconnect :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> Maybe (GClosure b) -> m Bool
 - accelGroupDisconnectKey :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> Word32 -> [ModifierType] -> m Bool
 - accelGroupFind :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> AccelGroupFindFunc -> m AccelKey
 - accelGroupFromAccelClosure :: (HasCallStack, MonadIO m) => GClosure a -> m (Maybe AccelGroup)
 - accelGroupGetIsLocked :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> m Bool
 - accelGroupGetModifierMask :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> m [ModifierType]
 - accelGroupLock :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> m ()
 - accelGroupNew :: (HasCallStack, MonadIO m) => m AccelGroup
 - accelGroupQuery :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> Word32 -> [ModifierType] -> m (Maybe [AccelGroupEntry])
 - accelGroupUnlock :: (HasCallStack, MonadIO m, IsAccelGroup a) => a -> m ()
 - getAccelGroupIsLocked :: (MonadIO m, IsAccelGroup o) => o -> m Bool
 - getAccelGroupModifierMask :: (MonadIO m, IsAccelGroup o) => o -> m [ModifierType]
 - type AccelGroupAccelActivateCallback = Object -> Word32 -> [ModifierType] -> IO Bool
 - type C_AccelGroupAccelActivateCallback = Ptr () -> Ptr Object -> Word32 -> CUInt -> Ptr () -> IO CInt
 - afterAccelGroupAccelActivate :: (IsAccelGroup a, MonadIO m) => a -> Maybe Text -> AccelGroupAccelActivateCallback -> m SignalHandlerId
 - genClosure_AccelGroupAccelActivate :: MonadIO m => AccelGroupAccelActivateCallback -> m (GClosure C_AccelGroupAccelActivateCallback)
 - mk_AccelGroupAccelActivateCallback :: C_AccelGroupAccelActivateCallback -> IO (FunPtr C_AccelGroupAccelActivateCallback)
 - noAccelGroupAccelActivateCallback :: Maybe AccelGroupAccelActivateCallback
 - onAccelGroupAccelActivate :: (IsAccelGroup a, MonadIO m) => a -> Maybe Text -> AccelGroupAccelActivateCallback -> m SignalHandlerId
 - wrap_AccelGroupAccelActivateCallback :: AccelGroupAccelActivateCallback -> C_AccelGroupAccelActivateCallback
 - type AccelGroupAccelChangedCallback = Word32 -> [ModifierType] -> GClosure () -> IO ()
 - type C_AccelGroupAccelChangedCallback = Ptr () -> Word32 -> CUInt -> Ptr (GClosure ()) -> Ptr () -> IO ()
 - afterAccelGroupAccelChanged :: (IsAccelGroup a, MonadIO m) => a -> Maybe Text -> AccelGroupAccelChangedCallback -> m SignalHandlerId
 - genClosure_AccelGroupAccelChanged :: MonadIO m => AccelGroupAccelChangedCallback -> m (GClosure C_AccelGroupAccelChangedCallback)
 - mk_AccelGroupAccelChangedCallback :: C_AccelGroupAccelChangedCallback -> IO (FunPtr C_AccelGroupAccelChangedCallback)
 - noAccelGroupAccelChangedCallback :: Maybe AccelGroupAccelChangedCallback
 - onAccelGroupAccelChanged :: (IsAccelGroup a, MonadIO m) => a -> Maybe Text -> AccelGroupAccelChangedCallback -> m SignalHandlerId
 - wrap_AccelGroupAccelChangedCallback :: AccelGroupAccelChangedCallback -> C_AccelGroupAccelChangedCallback
 
Exported types
newtype AccelGroup Source #
Memory-managed wrapper type.
Constructors
| AccelGroup (ManagedPtr AccelGroup) | 
Instances
| Eq AccelGroup Source # | |
Defined in GI.Gtk.Objects.AccelGroup  | |
| IsGValue AccelGroup Source # | Convert   | 
Defined in GI.Gtk.Objects.AccelGroup  | |
| GObject AccelGroup Source # | |
Defined in GI.Gtk.Objects.AccelGroup Methods gobjectType :: IO GType #  | |
| HasParentTypes AccelGroup Source # | |
Defined in GI.Gtk.Objects.AccelGroup  | |
| type ParentTypes AccelGroup Source # | |
Defined in GI.Gtk.Objects.AccelGroup  | |
class (GObject o, IsDescendantOf AccelGroup o) => IsAccelGroup o Source #
Type class for types which can be safely cast to AccelGroup, for instance with toAccelGroup.
Instances
| (GObject o, IsDescendantOf AccelGroup o) => IsAccelGroup o Source # | |
Defined in GI.Gtk.Objects.AccelGroup  | |
toAccelGroup :: (MonadIO m, IsAccelGroup o) => o -> m AccelGroup Source #
Cast to AccelGroup, for types for which this is known to be safe. For general casts, use castTo.
Methods
Overloaded methods
activate
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a, IsObject b) | |
| => a | 
  | 
| -> Word32 | 
  | 
| -> b | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Bool | Returns:   | 
Finds the first accelerator in accelGroup that matches
 accelKey and accelMods, and activates it.
connect
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> [AccelFlags] | 
  | 
| -> GClosure C_AccelGroupActivate | 
  | 
| -> m () | 
Installs an accelerator in this group. When accelGroup is being
 activated in response to a call to accelGroupsActivate,
 closure will be invoked if the accelKey and accelMods from
 accelGroupsActivate match those of this connection.
The signature used for the closure is that of AccelGroupActivate.
Note that, due to implementation details, a single closure can only be connected to one accelerator group.
connectByPath
accelGroupConnectByPath Source #
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> Text | 
  | 
| -> GClosure b | 
  | 
| -> m () | 
Installs an accelerator in this group, using an accelerator path
 to look up the appropriate key and modifiers (see
 accelMapAddEntry). When accelGroup is being activated
 in response to a call to accelGroupsActivate, closure will
 be invoked if the accelKey and accelMods from
 accelGroupsActivate match the key and modifiers for the path.
The signature used for the closure is that of AccelGroupActivate.
Note that accelPath string will be stored in a GQuark. Therefore,
 if you pass a static string, you can save some memory by interning it
 first with internStaticString.
disconnect
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> Maybe (GClosure b) | 
  | 
| -> m Bool | Returns:   | 
Removes an accelerator previously installed through
 accelGroupConnect.
Since 2.20 closure can be Nothing.
disconnectKey
accelGroupDisconnectKey Source #
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m Bool | Returns:   | 
Removes an accelerator previously installed through
 accelGroupConnect.
find
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> AccelGroupFindFunc | 
  | 
| -> m AccelKey | Returns: the key of the first entry passing
      | 
Finds the first entry in an accelerator group for which
 findFunc returns True and returns its AccelKey.
fromAccelClosure
accelGroupFromAccelClosure Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => GClosure a | 
  | 
| -> m (Maybe AccelGroup) | Returns: the   | 
Finds the AccelGroup to which closure is connected;
 see accelGroupConnect.
getIsLocked
accelGroupGetIsLocked Source #
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> m Bool | Returns:   | 
Locks are added and removed using accelGroupLock and
 accelGroupUnlock.
Since: 2.14
getModifierMask
accelGroupGetModifierMask Source #
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> m [ModifierType] | Returns: the modifier mask for this accel group.  | 
Gets a ModifierType representing the mask for this
 accelGroup. For example, GDK_CONTROL_MASK, GDK_SHIFT_MASK, etc.
Since: 2.14
lock
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> m () | 
Locks the given accelerator group.
Locking an acelerator group prevents the accelerators contained
 within it to be changed during runtime. Refer to
 accelMapChangeEntry about runtime accelerator changes.
If called more than once, accelGroup remains locked until
 accelGroupUnlock has been called an equivalent number
 of times.
new
Arguments
| :: (HasCallStack, MonadIO m) | |
| => m AccelGroup | Returns: a new   | 
Creates a new AccelGroup.
query
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> m (Maybe [AccelGroupEntry]) | Returns: an array of
       | 
Queries an accelerator group for all entries matching accelKey
 and accelMods.
unlock
Arguments
| :: (HasCallStack, MonadIO m, IsAccelGroup a) | |
| => a | 
  | 
| -> m () | 
Undoes the last call to accelGroupLock on this accelGroup.
Properties
isLocked
No description available in the introspection data.
getAccelGroupIsLocked :: (MonadIO m, IsAccelGroup o) => o -> m Bool Source #
Get the value of the “is-locked” property.
 When overloading is enabled, this is equivalent to
get accelGroup #isLocked
modifierMask
No description available in the introspection data.
getAccelGroupModifierMask :: (MonadIO m, IsAccelGroup o) => o -> m [ModifierType] Source #
Get the value of the “modifier-mask” property.
 When overloading is enabled, this is equivalent to
get accelGroup #modifierMask
Signals
accelActivate
type AccelGroupAccelActivateCallback Source #
Arguments
| = Object | 
  | 
| -> Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> IO Bool | Returns:   | 
The accel-activate signal is an implementation detail of
 AccelGroup and not meant to be used by applications.
type C_AccelGroupAccelActivateCallback = Ptr () -> Ptr Object -> Word32 -> CUInt -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
afterAccelGroupAccelActivate :: (IsAccelGroup a, MonadIO m) => a -> Maybe Text -> AccelGroupAccelActivateCallback -> m SignalHandlerId Source #
Connect a signal handler for the accelActivate signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after accelGroup #accelActivate callback
This signal admits a optional parameter detail.
 If it's not Nothing, we will connect to “accel-activate::detail” instead.
genClosure_AccelGroupAccelActivate :: MonadIO m => AccelGroupAccelActivateCallback -> m (GClosure C_AccelGroupAccelActivateCallback) Source #
Wrap the callback into a GClosure.
mk_AccelGroupAccelActivateCallback :: C_AccelGroupAccelActivateCallback -> IO (FunPtr C_AccelGroupAccelActivateCallback) Source #
Generate a function pointer callable from C code, from a C_AccelGroupAccelActivateCallback.
noAccelGroupAccelActivateCallback :: Maybe AccelGroupAccelActivateCallback Source #
A convenience synonym for .Nothing :: Maybe AccelGroupAccelActivateCallback
onAccelGroupAccelActivate :: (IsAccelGroup a, MonadIO m) => a -> Maybe Text -> AccelGroupAccelActivateCallback -> m SignalHandlerId Source #
Connect a signal handler for the accelActivate signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on accelGroup #accelActivate callback
This signal admits a optional parameter detail.
 If it's not Nothing, we will connect to “accel-activate::detail” instead.
wrap_AccelGroupAccelActivateCallback :: AccelGroupAccelActivateCallback -> C_AccelGroupAccelActivateCallback Source #
Wrap a AccelGroupAccelActivateCallback into a C_AccelGroupAccelActivateCallback.
accelChanged
type AccelGroupAccelChangedCallback Source #
Arguments
| = Word32 | 
  | 
| -> [ModifierType] | 
  | 
| -> GClosure () | 
  | 
| -> IO () | 
The accel-changed signal is emitted when an entry is added to or removed from the accel group.
Widgets like AccelLabel which display an associated
 accelerator should connect to this signal, and rebuild
 their visual representation if the accelClosure is theirs.
type C_AccelGroupAccelChangedCallback = Ptr () -> Word32 -> CUInt -> Ptr (GClosure ()) -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
afterAccelGroupAccelChanged :: (IsAccelGroup a, MonadIO m) => a -> Maybe Text -> AccelGroupAccelChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the accelChanged signal, to be run after the default handler. When overloading is enabled, this is equivalent to
after accelGroup #accelChanged callback
This signal admits a optional parameter detail.
 If it's not Nothing, we will connect to “accel-changed::detail” instead.
genClosure_AccelGroupAccelChanged :: MonadIO m => AccelGroupAccelChangedCallback -> m (GClosure C_AccelGroupAccelChangedCallback) Source #
Wrap the callback into a GClosure.
mk_AccelGroupAccelChangedCallback :: C_AccelGroupAccelChangedCallback -> IO (FunPtr C_AccelGroupAccelChangedCallback) Source #
Generate a function pointer callable from C code, from a C_AccelGroupAccelChangedCallback.
noAccelGroupAccelChangedCallback :: Maybe AccelGroupAccelChangedCallback Source #
A convenience synonym for .Nothing :: Maybe AccelGroupAccelChangedCallback
onAccelGroupAccelChanged :: (IsAccelGroup a, MonadIO m) => a -> Maybe Text -> AccelGroupAccelChangedCallback -> m SignalHandlerId Source #
Connect a signal handler for the accelChanged signal, to be run before the default handler. When overloading is enabled, this is equivalent to
on accelGroup #accelChanged callback
This signal admits a optional parameter detail.
 If it's not Nothing, we will connect to “accel-changed::detail” instead.