Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria (inaki@blueleaf.cc) |
Safe Haskell | None |
Language | Haskell2010 |
Each key binding element of a binding sets binding list is represented by a GtkBindingEntry.
Synopsis
- newtype BindingEntry = BindingEntry (ManagedPtr BindingEntry)
- newZeroBindingEntry :: MonadIO m => m BindingEntry
- noBindingEntry :: Maybe BindingEntry
- bindingEntryAddSignalFromString :: (HasCallStack, MonadIO m) => BindingSet -> Text -> m TokenType
- bindingEntryAddSignall :: (HasCallStack, MonadIO m) => BindingSet -> Word32 -> [ModifierType] -> Text -> [BindingArg] -> m ()
- bindingEntryRemove :: (HasCallStack, MonadIO m) => BindingSet -> Word32 -> [ModifierType] -> m ()
- bindingEntrySkip :: (HasCallStack, MonadIO m) => BindingSet -> Word32 -> [ModifierType] -> m ()
- clearBindingEntryBindingSet :: MonadIO m => BindingEntry -> m ()
- getBindingEntryBindingSet :: MonadIO m => BindingEntry -> m (Maybe BindingSet)
- setBindingEntryBindingSet :: MonadIO m => BindingEntry -> Ptr BindingSet -> m ()
- getBindingEntryDestroyed :: MonadIO m => BindingEntry -> m Word32
- setBindingEntryDestroyed :: MonadIO m => BindingEntry -> Word32 -> m ()
- clearBindingEntryHashNext :: MonadIO m => BindingEntry -> m ()
- getBindingEntryHashNext :: MonadIO m => BindingEntry -> m (Maybe BindingEntry)
- setBindingEntryHashNext :: MonadIO m => BindingEntry -> Ptr BindingEntry -> m ()
- getBindingEntryInEmission :: MonadIO m => BindingEntry -> m Word32
- setBindingEntryInEmission :: MonadIO m => BindingEntry -> Word32 -> m ()
- getBindingEntryKeyval :: MonadIO m => BindingEntry -> m Word32
- setBindingEntryKeyval :: MonadIO m => BindingEntry -> Word32 -> m ()
- getBindingEntryMarksUnbound :: MonadIO m => BindingEntry -> m Word32
- setBindingEntryMarksUnbound :: MonadIO m => BindingEntry -> Word32 -> m ()
- getBindingEntryModifiers :: MonadIO m => BindingEntry -> m [ModifierType]
- setBindingEntryModifiers :: MonadIO m => BindingEntry -> [ModifierType] -> m ()
- clearBindingEntrySetNext :: MonadIO m => BindingEntry -> m ()
- getBindingEntrySetNext :: MonadIO m => BindingEntry -> m (Maybe BindingEntry)
- setBindingEntrySetNext :: MonadIO m => BindingEntry -> Ptr BindingEntry -> m ()
- clearBindingEntrySignals :: MonadIO m => BindingEntry -> m ()
- getBindingEntrySignals :: MonadIO m => BindingEntry -> m (Maybe BindingSignal)
- setBindingEntrySignals :: MonadIO m => BindingEntry -> Ptr BindingSignal -> m ()
Exported types
newtype BindingEntry Source #
Memory-managed wrapper type.
Instances
WrappedPtr BindingEntry Source # | |
Defined in GI.Gtk.Structs.BindingEntry | |
tag ~ AttrSet => Constructible BindingEntry tag Source # | |
Defined in GI.Gtk.Structs.BindingEntry new :: MonadIO m => (ManagedPtr BindingEntry -> BindingEntry) -> [AttrOp BindingEntry tag] -> m BindingEntry # |
newZeroBindingEntry :: MonadIO m => m BindingEntry Source #
Construct a BindingEntry
struct initialized to zero.
noBindingEntry :: Maybe BindingEntry Source #
A convenience alias for Nothing
:: Maybe
BindingEntry
.
Methods
addSignalFromString
bindingEntryAddSignalFromString Source #
:: (HasCallStack, MonadIO m) | |
=> BindingSet |
|
-> Text |
|
-> m TokenType | Returns: |
Parses a signal description from signalDesc
and incorporates
it into bindingSet
.
Signal descriptions may either bind a key combination to one or more signals: > > bind "key" { > "signalname" (param, ...) > ... > }
Or they may also unbind a key combination: > > unbind "key"
Key combinations must be in a format that can be parsed by
acceleratorParse
.
Since: 3.0
addSignall
bindingEntryAddSignall Source #
:: (HasCallStack, MonadIO m) | |
=> BindingSet |
|
-> Word32 |
|
-> [ModifierType] |
|
-> Text |
|
-> [BindingArg] |
|
-> m () |
Override or install a new key binding for keyval
with modifiers
on
bindingSet
.
remove
:: (HasCallStack, MonadIO m) | |
=> BindingSet |
|
-> Word32 |
|
-> [ModifierType] |
|
-> m () |
Remove a binding previously installed via
gtk_binding_entry_add_signal()
on bindingSet
.
skip
:: (HasCallStack, MonadIO m) | |
=> BindingSet |
|
-> Word32 |
|
-> [ModifierType] |
|
-> m () |
Install a binding on bindingSet
which causes key lookups
to be aborted, to prevent bindings from lower priority sets
to be activated.
Since: 2.12
Properties
bindingSet
binding set this entry belongs to
clearBindingEntryBindingSet :: MonadIO m => BindingEntry -> m () Source #
Set the value of the “binding_set
” field to Nothing
.
When overloading is enabled, this is equivalent to
clear
#bindingSet
getBindingEntryBindingSet :: MonadIO m => BindingEntry -> m (Maybe BindingSet) Source #
Get the value of the “binding_set
” field.
When overloading is enabled, this is equivalent to
get
bindingEntry #bindingSet
setBindingEntryBindingSet :: MonadIO m => BindingEntry -> Ptr BindingSet -> m () Source #
Set the value of the “binding_set
” field.
When overloading is enabled, this is equivalent to
set
bindingEntry [ #bindingSet:=
value ]
destroyed
implementation detail
getBindingEntryDestroyed :: MonadIO m => BindingEntry -> m Word32 Source #
Get the value of the “destroyed
” field.
When overloading is enabled, this is equivalent to
get
bindingEntry #destroyed
setBindingEntryDestroyed :: MonadIO m => BindingEntry -> Word32 -> m () Source #
Set the value of the “destroyed
” field.
When overloading is enabled, this is equivalent to
set
bindingEntry [ #destroyed:=
value ]
hashNext
implementation detail
clearBindingEntryHashNext :: MonadIO m => BindingEntry -> m () Source #
Set the value of the “hash_next
” field to Nothing
.
When overloading is enabled, this is equivalent to
clear
#hashNext
getBindingEntryHashNext :: MonadIO m => BindingEntry -> m (Maybe BindingEntry) Source #
Get the value of the “hash_next
” field.
When overloading is enabled, this is equivalent to
get
bindingEntry #hashNext
setBindingEntryHashNext :: MonadIO m => BindingEntry -> Ptr BindingEntry -> m () Source #
Set the value of the “hash_next
” field.
When overloading is enabled, this is equivalent to
set
bindingEntry [ #hashNext:=
value ]
inEmission
implementation detail
getBindingEntryInEmission :: MonadIO m => BindingEntry -> m Word32 Source #
Get the value of the “in_emission
” field.
When overloading is enabled, this is equivalent to
get
bindingEntry #inEmission
setBindingEntryInEmission :: MonadIO m => BindingEntry -> Word32 -> m () Source #
Set the value of the “in_emission
” field.
When overloading is enabled, this is equivalent to
set
bindingEntry [ #inEmission:=
value ]
keyval
key value to match
getBindingEntryKeyval :: MonadIO m => BindingEntry -> m Word32 Source #
Get the value of the “keyval
” field.
When overloading is enabled, this is equivalent to
get
bindingEntry #keyval
setBindingEntryKeyval :: MonadIO m => BindingEntry -> Word32 -> m () Source #
Set the value of the “keyval
” field.
When overloading is enabled, this is equivalent to
set
bindingEntry [ #keyval:=
value ]
marksUnbound
implementation detail
getBindingEntryMarksUnbound :: MonadIO m => BindingEntry -> m Word32 Source #
Get the value of the “marks_unbound
” field.
When overloading is enabled, this is equivalent to
get
bindingEntry #marksUnbound
setBindingEntryMarksUnbound :: MonadIO m => BindingEntry -> Word32 -> m () Source #
Set the value of the “marks_unbound
” field.
When overloading is enabled, this is equivalent to
set
bindingEntry [ #marksUnbound:=
value ]
modifiers
key modifiers to match
getBindingEntryModifiers :: MonadIO m => BindingEntry -> m [ModifierType] Source #
Get the value of the “modifiers
” field.
When overloading is enabled, this is equivalent to
get
bindingEntry #modifiers
setBindingEntryModifiers :: MonadIO m => BindingEntry -> [ModifierType] -> m () Source #
Set the value of the “modifiers
” field.
When overloading is enabled, this is equivalent to
set
bindingEntry [ #modifiers:=
value ]
setNext
linked list of entries maintained by binding set
clearBindingEntrySetNext :: MonadIO m => BindingEntry -> m () Source #
Set the value of the “set_next
” field to Nothing
.
When overloading is enabled, this is equivalent to
clear
#setNext
getBindingEntrySetNext :: MonadIO m => BindingEntry -> m (Maybe BindingEntry) Source #
Get the value of the “set_next
” field.
When overloading is enabled, this is equivalent to
get
bindingEntry #setNext
setBindingEntrySetNext :: MonadIO m => BindingEntry -> Ptr BindingEntry -> m () Source #
Set the value of the “set_next
” field.
When overloading is enabled, this is equivalent to
set
bindingEntry [ #setNext:=
value ]
signals
action signals of this entry
clearBindingEntrySignals :: MonadIO m => BindingEntry -> m () Source #
Set the value of the “signals
” field to Nothing
.
When overloading is enabled, this is equivalent to
clear
#signals
getBindingEntrySignals :: MonadIO m => BindingEntry -> m (Maybe BindingSignal) Source #
Get the value of the “signals
” field.
When overloading is enabled, this is equivalent to
get
bindingEntry #signals
setBindingEntrySignals :: MonadIO m => BindingEntry -> Ptr BindingSignal -> m () Source #
Set the value of the “signals
” field.
When overloading is enabled, this is equivalent to
set
bindingEntry [ #signals:=
value ]