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 |
Synopsis
- type C_EventListener = Ptr Object -> IO ()
- type EventListener = Object -> IO ()
- dynamic_EventListener :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_EventListener -> a -> m ()
- genClosure_EventListener :: MonadIO m => EventListener -> m (GClosure C_EventListener)
- mk_EventListener :: C_EventListener -> IO (FunPtr C_EventListener)
- noEventListener :: Maybe EventListener
- wrap_EventListener :: Maybe (Ptr (FunPtr C_EventListener)) -> EventListener -> C_EventListener
- type C_EventListenerInit = IO ()
- type EventListenerInit = IO ()
- dynamic_EventListenerInit :: (HasCallStack, MonadIO m) => FunPtr C_EventListenerInit -> m ()
- genClosure_EventListenerInit :: MonadIO m => EventListenerInit -> m (GClosure C_EventListenerInit)
- mk_EventListenerInit :: C_EventListenerInit -> IO (FunPtr C_EventListenerInit)
- noEventListenerInit :: Maybe EventListenerInit
- wrap_EventListenerInit :: Maybe (Ptr (FunPtr C_EventListenerInit)) -> EventListenerInit -> C_EventListenerInit
- type C_FocusHandler = Ptr Object -> CInt -> IO ()
- type FocusHandler = Object -> Bool -> IO ()
- dynamic_FocusHandler :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_FocusHandler -> a -> Bool -> m ()
- genClosure_FocusHandler :: MonadIO m => FocusHandler -> m (GClosure C_FocusHandler)
- mk_FocusHandler :: C_FocusHandler -> IO (FunPtr C_FocusHandler)
- noFocusHandler :: Maybe FocusHandler
- wrap_FocusHandler :: Maybe (Ptr (FunPtr C_FocusHandler)) -> FocusHandler -> C_FocusHandler
- type C_Function = Ptr () -> IO CInt
- type Function = IO Bool
- type Function_WithClosures = Ptr () -> IO Bool
- drop_closures_Function :: Function -> Function_WithClosures
- dynamic_Function :: (HasCallStack, MonadIO m) => FunPtr C_Function -> Ptr () -> m Bool
- genClosure_Function :: MonadIO m => Function -> m (GClosure C_Function)
- mk_Function :: C_Function -> IO (FunPtr C_Function)
- noFunction :: Maybe Function
- noFunction_WithClosures :: Maybe Function_WithClosures
- wrap_Function :: Maybe (Ptr (FunPtr C_Function)) -> Function_WithClosures -> C_Function
- type C_KeySnoopFunc = Ptr KeyEventStruct -> Ptr () -> IO Int32
- type KeySnoopFunc = KeyEventStruct -> IO Int32
- type KeySnoopFunc_WithClosures = KeyEventStruct -> Ptr () -> IO Int32
- drop_closures_KeySnoopFunc :: KeySnoopFunc -> KeySnoopFunc_WithClosures
- dynamic_KeySnoopFunc :: (HasCallStack, MonadIO m) => FunPtr C_KeySnoopFunc -> KeyEventStruct -> Ptr () -> m Int32
- genClosure_KeySnoopFunc :: MonadIO m => KeySnoopFunc -> m (GClosure C_KeySnoopFunc)
- mk_KeySnoopFunc :: C_KeySnoopFunc -> IO (FunPtr C_KeySnoopFunc)
- noKeySnoopFunc :: Maybe KeySnoopFunc
- noKeySnoopFunc_WithClosures :: Maybe KeySnoopFunc_WithClosures
- wrap_KeySnoopFunc :: Maybe (Ptr (FunPtr C_KeySnoopFunc)) -> KeySnoopFunc_WithClosures -> C_KeySnoopFunc
- type C_PropertyChangeHandler = Ptr Object -> Ptr PropertyValues -> IO ()
- type PropertyChangeHandler = Object -> PropertyValues -> IO ()
- dynamic_PropertyChangeHandler :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_PropertyChangeHandler -> a -> PropertyValues -> m ()
- genClosure_PropertyChangeHandler :: MonadIO m => PropertyChangeHandler -> m (GClosure C_PropertyChangeHandler)
- mk_PropertyChangeHandler :: C_PropertyChangeHandler -> IO (FunPtr C_PropertyChangeHandler)
- noPropertyChangeHandler :: Maybe PropertyChangeHandler
- wrap_PropertyChangeHandler :: Maybe (Ptr (FunPtr C_PropertyChangeHandler)) -> PropertyChangeHandler -> C_PropertyChangeHandler
Signals
EventListener
type EventListener Source #
= Object |
|
-> IO () |
A function which is called when an object emits a matching event,
as used in atk_add_focus_tracker
.
Currently the only events for which object-specific handlers are
supported are events of type "focus:". Most clients of ATK will prefer to
attach signal handlers for the various ATK signals instead.
see atk_add_focus_tracker.
dynamic_EventListener Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_EventListener | |
-> a |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_EventListener :: MonadIO m => EventListener -> m (GClosure C_EventListener) Source #
Wrap the callback into a GClosure
.
mk_EventListener :: C_EventListener -> IO (FunPtr C_EventListener) Source #
Generate a function pointer callable from C code, from a C_EventListener
.
noEventListener :: Maybe EventListener Source #
A convenience synonym for
.Nothing
:: Maybe
EventListener
wrap_EventListener :: Maybe (Ptr (FunPtr C_EventListener)) -> EventListener -> C_EventListener Source #
Wrap a EventListener
into a C_EventListener
.
EventListenerInit
type C_EventListenerInit = IO () Source #
Type for the callback on the (unwrapped) C side.
type EventListenerInit = IO () Source #
An EventListenerInit
function is a special function that is
called in order to initialize the per-object event registration system
used by EventListener
, if any preparation is required.
see atk_focus_tracker_init.
dynamic_EventListenerInit :: (HasCallStack, MonadIO m) => FunPtr C_EventListenerInit -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_EventListenerInit :: MonadIO m => EventListenerInit -> m (GClosure C_EventListenerInit) Source #
Wrap the callback into a GClosure
.
mk_EventListenerInit :: C_EventListenerInit -> IO (FunPtr C_EventListenerInit) Source #
Generate a function pointer callable from C code, from a C_EventListenerInit
.
noEventListenerInit :: Maybe EventListenerInit Source #
A convenience synonym for
.Nothing
:: Maybe
EventListenerInit
wrap_EventListenerInit :: Maybe (Ptr (FunPtr C_EventListenerInit)) -> EventListenerInit -> C_EventListenerInit Source #
Wrap a EventListenerInit
into a C_EventListenerInit
.
FocusHandler
type C_FocusHandler = Ptr Object -> CInt -> IO () Source #
Type for the callback on the (unwrapped) C side.
type FocusHandler Source #
= Object |
|
-> Bool |
|
-> IO () |
Deprecated: (Since version 2.9.4)Deprecated with atk_component_add_focus_handler()
and componentRemoveFocusHandler
. See thosemethods for more information.
The type of callback function used for
atk_component_add_focus_handler()
and
componentRemoveFocusHandler
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_FocusHandler | |
-> a |
|
-> Bool |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FocusHandler :: MonadIO m => FocusHandler -> m (GClosure C_FocusHandler) Source #
Wrap the callback into a GClosure
.
mk_FocusHandler :: C_FocusHandler -> IO (FunPtr C_FocusHandler) Source #
Generate a function pointer callable from C code, from a C_FocusHandler
.
noFocusHandler :: Maybe FocusHandler Source #
A convenience synonym for
.Nothing
:: Maybe
FocusHandler
wrap_FocusHandler :: Maybe (Ptr (FunPtr C_FocusHandler)) -> FocusHandler -> C_FocusHandler Source #
Wrap a FocusHandler
into a C_FocusHandler
.
Function
An AtkFunction is a function definition used for padding which has been added to class and interface structures to allow for expansion in the future.
type Function_WithClosures Source #
An AtkFunction is a function definition used for padding which has been added to class and interface structures to allow for expansion in the future.
drop_closures_Function :: Function -> Function_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_Function | |
-> Ptr () |
|
-> m Bool | Returns: not used |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_Function :: MonadIO m => Function -> m (GClosure C_Function) Source #
Wrap the callback into a GClosure
.
mk_Function :: C_Function -> IO (FunPtr C_Function) Source #
Generate a function pointer callable from C code, from a C_Function
.
noFunction_WithClosures :: Maybe Function_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
Function_WithClosures
wrap_Function :: Maybe (Ptr (FunPtr C_Function)) -> Function_WithClosures -> C_Function Source #
Wrap a Function
into a C_Function
.
KeySnoopFunc
type C_KeySnoopFunc = Ptr KeyEventStruct -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type KeySnoopFunc Source #
= KeyEventStruct |
|
-> IO Int32 | Returns: TRUE (nonzero) if the event emission should be stopped and the event discarded without being passed to the normal GUI recipient; FALSE (zero) if the event dispatch to the client application should proceed as normal. see atk_add_key_event_listener. |
An KeySnoopFunc
is a type of callback which is called whenever a key event occurs,
if registered via atk_add_key_event_listener. It allows for pre-emptive
interception of key events via the return code as described below.
type KeySnoopFunc_WithClosures Source #
= KeyEventStruct |
|
-> Ptr () |
|
-> IO Int32 | Returns: TRUE (nonzero) if the event emission should be stopped and the event discarded without being passed to the normal GUI recipient; FALSE (zero) if the event dispatch to the client application should proceed as normal. see atk_add_key_event_listener. |
An KeySnoopFunc
is a type of callback which is called whenever a key event occurs,
if registered via atk_add_key_event_listener. It allows for pre-emptive
interception of key events via the return code as described below.
drop_closures_KeySnoopFunc :: KeySnoopFunc -> KeySnoopFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_KeySnoopFunc | |
-> KeyEventStruct |
|
-> Ptr () |
|
-> m Int32 | Returns: TRUE (nonzero) if the event emission should be stopped and the event discarded without being passed to the normal GUI recipient; FALSE (zero) if the event dispatch to the client application should proceed as normal. see atk_add_key_event_listener. |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_KeySnoopFunc :: MonadIO m => KeySnoopFunc -> m (GClosure C_KeySnoopFunc) Source #
Wrap the callback into a GClosure
.
mk_KeySnoopFunc :: C_KeySnoopFunc -> IO (FunPtr C_KeySnoopFunc) Source #
Generate a function pointer callable from C code, from a C_KeySnoopFunc
.
noKeySnoopFunc :: Maybe KeySnoopFunc Source #
A convenience synonym for
.Nothing
:: Maybe
KeySnoopFunc
noKeySnoopFunc_WithClosures :: Maybe KeySnoopFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
KeySnoopFunc_WithClosures
wrap_KeySnoopFunc :: Maybe (Ptr (FunPtr C_KeySnoopFunc)) -> KeySnoopFunc_WithClosures -> C_KeySnoopFunc Source #
Wrap a KeySnoopFunc
into a C_KeySnoopFunc
.
PropertyChangeHandler
type C_PropertyChangeHandler = Ptr Object -> Ptr PropertyValues -> IO () Source #
Type for the callback on the (unwrapped) C side.
type PropertyChangeHandler Source #
= Object |
|
-> PropertyValues |
|
-> IO () |
Deprecated: Since 2.12.
An AtkPropertyChangeHandler is a function which is executed when an
AtkObject's property changes value. It is specified in a call to
atk_object_connect_property_change_handler()
.
dynamic_PropertyChangeHandler Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_PropertyChangeHandler | |
-> a |
|
-> PropertyValues |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PropertyChangeHandler :: MonadIO m => PropertyChangeHandler -> m (GClosure C_PropertyChangeHandler) Source #
Wrap the callback into a GClosure
.
mk_PropertyChangeHandler :: C_PropertyChangeHandler -> IO (FunPtr C_PropertyChangeHandler) Source #
Generate a function pointer callable from C code, from a C_PropertyChangeHandler
.
noPropertyChangeHandler :: Maybe PropertyChangeHandler Source #
A convenience synonym for
.Nothing
:: Maybe
PropertyChangeHandler