Copyright | Will Thompson and Iñaki García Etxebarria |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type ActorCreateChildFunc = Object -> IO Actor
- type ActorCreateChildFunc_WithClosures = Object -> Ptr () -> IO Actor
- type C_ActorCreateChildFunc = Ptr Object -> Ptr () -> IO (Ptr Actor)
- drop_closures_ActorCreateChildFunc :: ActorCreateChildFunc -> ActorCreateChildFunc_WithClosures
- dynamic_ActorCreateChildFunc :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_ActorCreateChildFunc -> a -> Ptr () -> m Actor
- genClosure_ActorCreateChildFunc :: MonadIO m => ActorCreateChildFunc -> m (GClosure C_ActorCreateChildFunc)
- mk_ActorCreateChildFunc :: C_ActorCreateChildFunc -> IO (FunPtr C_ActorCreateChildFunc)
- noActorCreateChildFunc :: Maybe ActorCreateChildFunc
- noActorCreateChildFunc_WithClosures :: Maybe ActorCreateChildFunc_WithClosures
- wrap_ActorCreateChildFunc :: Maybe (Ptr (FunPtr C_ActorCreateChildFunc)) -> ActorCreateChildFunc_WithClosures -> C_ActorCreateChildFunc
- type AlphaFunc = Alpha -> IO Double
- type AlphaFunc_WithClosures = Alpha -> Ptr () -> IO Double
- type C_AlphaFunc = Ptr Alpha -> Ptr () -> IO CDouble
- drop_closures_AlphaFunc :: AlphaFunc -> AlphaFunc_WithClosures
- dynamic_AlphaFunc :: (HasCallStack, MonadIO m, IsAlpha a) => FunPtr C_AlphaFunc -> a -> Ptr () -> m Double
- genClosure_AlphaFunc :: MonadIO m => AlphaFunc -> m (GClosure C_AlphaFunc)
- mk_AlphaFunc :: C_AlphaFunc -> IO (FunPtr C_AlphaFunc)
- noAlphaFunc :: Maybe AlphaFunc
- noAlphaFunc_WithClosures :: Maybe AlphaFunc_WithClosures
- wrap_AlphaFunc :: Maybe (Ptr (FunPtr C_AlphaFunc)) -> AlphaFunc_WithClosures -> C_AlphaFunc
- type BehaviourForeachFunc = Behaviour -> Actor -> IO ()
- type BehaviourForeachFunc_WithClosures = Behaviour -> Actor -> Ptr () -> IO ()
- type C_BehaviourForeachFunc = Ptr Behaviour -> Ptr Actor -> Ptr () -> IO ()
- drop_closures_BehaviourForeachFunc :: BehaviourForeachFunc -> BehaviourForeachFunc_WithClosures
- dynamic_BehaviourForeachFunc :: (HasCallStack, MonadIO m, IsBehaviour a, IsActor b) => FunPtr C_BehaviourForeachFunc -> a -> b -> Ptr () -> m ()
- genClosure_BehaviourForeachFunc :: MonadIO m => BehaviourForeachFunc -> m (GClosure C_BehaviourForeachFunc)
- mk_BehaviourForeachFunc :: C_BehaviourForeachFunc -> IO (FunPtr C_BehaviourForeachFunc)
- noBehaviourForeachFunc :: Maybe BehaviourForeachFunc
- noBehaviourForeachFunc_WithClosures :: Maybe BehaviourForeachFunc_WithClosures
- wrap_BehaviourForeachFunc :: Maybe (Ptr (FunPtr C_BehaviourForeachFunc)) -> BehaviourForeachFunc_WithClosures -> C_BehaviourForeachFunc
- type BindingActionFunc = Object -> Text -> Word32 -> [ModifierType] -> IO Bool
- type BindingActionFunc_WithClosures = Object -> Text -> Word32 -> [ModifierType] -> Ptr () -> IO Bool
- type C_BindingActionFunc = Ptr Object -> CString -> Word32 -> CUInt -> Ptr () -> IO CInt
- drop_closures_BindingActionFunc :: BindingActionFunc -> BindingActionFunc_WithClosures
- dynamic_BindingActionFunc :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_BindingActionFunc -> a -> Text -> Word32 -> [ModifierType] -> Ptr () -> m Bool
- genClosure_BindingActionFunc :: MonadIO m => BindingActionFunc -> m (GClosure C_BindingActionFunc)
- mk_BindingActionFunc :: C_BindingActionFunc -> IO (FunPtr C_BindingActionFunc)
- noBindingActionFunc :: Maybe BindingActionFunc
- noBindingActionFunc_WithClosures :: Maybe BindingActionFunc_WithClosures
- wrap_BindingActionFunc :: Maybe (Ptr (FunPtr C_BindingActionFunc)) -> BindingActionFunc_WithClosures -> C_BindingActionFunc
- type C_Callback = Ptr Actor -> Ptr () -> IO ()
- type Callback = Actor -> IO ()
- type Callback_WithClosures = Actor -> Ptr () -> IO ()
- drop_closures_Callback :: Callback -> Callback_WithClosures
- dynamic_Callback :: (HasCallStack, MonadIO m, IsActor a) => FunPtr C_Callback -> a -> Ptr () -> m ()
- genClosure_Callback :: MonadIO m => Callback -> m (GClosure C_Callback)
- mk_Callback :: C_Callback -> IO (FunPtr C_Callback)
- noCallback :: Maybe Callback
- noCallback_WithClosures :: Maybe Callback_WithClosures
- wrap_Callback :: Maybe (Ptr (FunPtr C_Callback)) -> Callback_WithClosures -> C_Callback
- type C_EventFilterFunc = Ptr Event -> Ptr () -> IO CInt
- type EventFilterFunc = Event -> IO Bool
- type EventFilterFunc_WithClosures = Event -> Ptr () -> IO Bool
- drop_closures_EventFilterFunc :: EventFilterFunc -> EventFilterFunc_WithClosures
- dynamic_EventFilterFunc :: (HasCallStack, MonadIO m) => FunPtr C_EventFilterFunc -> Event -> Ptr () -> m Bool
- genClosure_EventFilterFunc :: MonadIO m => EventFilterFunc -> m (GClosure C_EventFilterFunc)
- mk_EventFilterFunc :: C_EventFilterFunc -> IO (FunPtr C_EventFilterFunc)
- noEventFilterFunc :: Maybe EventFilterFunc
- noEventFilterFunc_WithClosures :: Maybe EventFilterFunc_WithClosures
- wrap_EventFilterFunc :: Maybe (Ptr (FunPtr C_EventFilterFunc)) -> EventFilterFunc_WithClosures -> C_EventFilterFunc
- type C_ModelFilterFunc = Ptr Model -> Ptr ModelIter -> Ptr () -> IO CInt
- type ModelFilterFunc = Model -> ModelIter -> IO Bool
- type ModelFilterFunc_WithClosures = Model -> ModelIter -> Ptr () -> IO Bool
- drop_closures_ModelFilterFunc :: ModelFilterFunc -> ModelFilterFunc_WithClosures
- dynamic_ModelFilterFunc :: (HasCallStack, MonadIO m, IsModel a, IsModelIter b) => FunPtr C_ModelFilterFunc -> a -> b -> Ptr () -> m Bool
- genClosure_ModelFilterFunc :: MonadIO m => ModelFilterFunc -> m (GClosure C_ModelFilterFunc)
- mk_ModelFilterFunc :: C_ModelFilterFunc -> IO (FunPtr C_ModelFilterFunc)
- noModelFilterFunc :: Maybe ModelFilterFunc
- noModelFilterFunc_WithClosures :: Maybe ModelFilterFunc_WithClosures
- wrap_ModelFilterFunc :: Maybe (Ptr (FunPtr C_ModelFilterFunc)) -> ModelFilterFunc_WithClosures -> C_ModelFilterFunc
- type C_ModelForeachFunc = Ptr Model -> Ptr ModelIter -> Ptr () -> IO CInt
- type ModelForeachFunc = Model -> ModelIter -> IO Bool
- type ModelForeachFunc_WithClosures = Model -> ModelIter -> Ptr () -> IO Bool
- drop_closures_ModelForeachFunc :: ModelForeachFunc -> ModelForeachFunc_WithClosures
- dynamic_ModelForeachFunc :: (HasCallStack, MonadIO m, IsModel a, IsModelIter b) => FunPtr C_ModelForeachFunc -> a -> b -> Ptr () -> m Bool
- genClosure_ModelForeachFunc :: MonadIO m => ModelForeachFunc -> m (GClosure C_ModelForeachFunc)
- mk_ModelForeachFunc :: C_ModelForeachFunc -> IO (FunPtr C_ModelForeachFunc)
- noModelForeachFunc :: Maybe ModelForeachFunc
- noModelForeachFunc_WithClosures :: Maybe ModelForeachFunc_WithClosures
- wrap_ModelForeachFunc :: Maybe (Ptr (FunPtr C_ModelForeachFunc)) -> ModelForeachFunc_WithClosures -> C_ModelForeachFunc
- type C_ModelSortFunc = Ptr Model -> Ptr GValue -> Ptr GValue -> Ptr () -> IO Int32
- type ModelSortFunc = Model -> GValue -> GValue -> IO Int32
- type ModelSortFunc_WithClosures = Model -> GValue -> GValue -> Ptr () -> IO Int32
- drop_closures_ModelSortFunc :: ModelSortFunc -> ModelSortFunc_WithClosures
- dynamic_ModelSortFunc :: (HasCallStack, MonadIO m, IsModel a) => FunPtr C_ModelSortFunc -> a -> GValue -> GValue -> Ptr () -> m Int32
- genClosure_ModelSortFunc :: MonadIO m => ModelSortFunc -> m (GClosure C_ModelSortFunc)
- mk_ModelSortFunc :: C_ModelSortFunc -> IO (FunPtr C_ModelSortFunc)
- noModelSortFunc :: Maybe ModelSortFunc
- noModelSortFunc_WithClosures :: Maybe ModelSortFunc_WithClosures
- wrap_ModelSortFunc :: Maybe (Ptr (FunPtr C_ModelSortFunc)) -> ModelSortFunc_WithClosures -> C_ModelSortFunc
- type C_PathCallback = Ptr PathNode -> Ptr () -> IO ()
- type PathCallback = PathNode -> IO ()
- type PathCallback_WithClosures = PathNode -> Ptr () -> IO ()
- drop_closures_PathCallback :: PathCallback -> PathCallback_WithClosures
- dynamic_PathCallback :: (HasCallStack, MonadIO m) => FunPtr C_PathCallback -> PathNode -> Ptr () -> m ()
- genClosure_PathCallback :: MonadIO m => PathCallback -> m (GClosure C_PathCallback)
- mk_PathCallback :: C_PathCallback -> IO (FunPtr C_PathCallback)
- noPathCallback :: Maybe PathCallback
- noPathCallback_WithClosures :: Maybe PathCallback_WithClosures
- wrap_PathCallback :: Maybe (Ptr (FunPtr C_PathCallback)) -> PathCallback_WithClosures -> C_PathCallback
- type C_ProgressFunc = Ptr GValue -> Ptr GValue -> CDouble -> Ptr GValue -> IO CInt
- type ProgressFunc = GValue -> GValue -> Double -> GValue -> IO Bool
- dynamic_ProgressFunc :: (HasCallStack, MonadIO m) => FunPtr C_ProgressFunc -> GValue -> GValue -> Double -> GValue -> m Bool
- genClosure_ProgressFunc :: MonadIO m => ProgressFunc -> m (GClosure C_ProgressFunc)
- mk_ProgressFunc :: C_ProgressFunc -> IO (FunPtr C_ProgressFunc)
- noProgressFunc :: Maybe ProgressFunc
- wrap_ProgressFunc :: Maybe (Ptr (FunPtr C_ProgressFunc)) -> ProgressFunc -> C_ProgressFunc
- type C_ScriptConnectFunc = Ptr Script -> Ptr Object -> CString -> CString -> Ptr Object -> CUInt -> Ptr () -> IO ()
- type ScriptConnectFunc = Script -> Object -> Text -> Text -> Object -> [ConnectFlags] -> IO ()
- type ScriptConnectFunc_WithClosures = Script -> Object -> Text -> Text -> Object -> [ConnectFlags] -> Ptr () -> IO ()
- drop_closures_ScriptConnectFunc :: ScriptConnectFunc -> ScriptConnectFunc_WithClosures
- dynamic_ScriptConnectFunc :: (HasCallStack, MonadIO m, IsScript a, IsObject b, IsObject c) => FunPtr C_ScriptConnectFunc -> a -> b -> Text -> Text -> c -> [ConnectFlags] -> Ptr () -> m ()
- genClosure_ScriptConnectFunc :: MonadIO m => ScriptConnectFunc -> m (GClosure C_ScriptConnectFunc)
- mk_ScriptConnectFunc :: C_ScriptConnectFunc -> IO (FunPtr C_ScriptConnectFunc)
- noScriptConnectFunc :: Maybe ScriptConnectFunc
- noScriptConnectFunc_WithClosures :: Maybe ScriptConnectFunc_WithClosures
- wrap_ScriptConnectFunc :: Maybe (Ptr (FunPtr C_ScriptConnectFunc)) -> ScriptConnectFunc_WithClosures -> C_ScriptConnectFunc
- type C_TimelineProgressFunc = Ptr Timeline -> CDouble -> CDouble -> Ptr () -> IO CDouble
- type TimelineProgressFunc = Timeline -> Double -> Double -> IO Double
- type TimelineProgressFunc_WithClosures = Timeline -> Double -> Double -> Ptr () -> IO Double
- drop_closures_TimelineProgressFunc :: TimelineProgressFunc -> TimelineProgressFunc_WithClosures
- dynamic_TimelineProgressFunc :: (HasCallStack, MonadIO m, IsTimeline a) => FunPtr C_TimelineProgressFunc -> a -> Double -> Double -> Ptr () -> m Double
- genClosure_TimelineProgressFunc :: MonadIO m => TimelineProgressFunc -> m (GClosure C_TimelineProgressFunc)
- mk_TimelineProgressFunc :: C_TimelineProgressFunc -> IO (FunPtr C_TimelineProgressFunc)
- noTimelineProgressFunc :: Maybe TimelineProgressFunc
- noTimelineProgressFunc_WithClosures :: Maybe TimelineProgressFunc_WithClosures
- wrap_TimelineProgressFunc :: Maybe (Ptr (FunPtr C_TimelineProgressFunc)) -> TimelineProgressFunc_WithClosures -> C_TimelineProgressFunc
Signals
ActorCreateChildFunc
type ActorCreateChildFunc Source #
Creates a Actor
using the item
in the model.
The usual way to implement this function is to create a Actor
instance and then bind the Object
properties to the actor properties
of interest, using objectBindProperty
. This way, when the item
in the ListModel
changes, the Actor
changes as well.
Since: 1.24
type ActorCreateChildFunc_WithClosures Source #
= Object |
|
-> Ptr () |
|
-> IO Actor | Returns: The newly created child |
Creates a Actor
using the item
in the model.
The usual way to implement this function is to create a Actor
instance and then bind the Object
properties to the actor properties
of interest, using objectBindProperty
. This way, when the item
in the ListModel
changes, the Actor
changes as well.
Since: 1.24
type C_ActorCreateChildFunc = Ptr Object -> Ptr () -> IO (Ptr Actor) Source #
Type for the callback on the (unwrapped) C side.
drop_closures_ActorCreateChildFunc :: ActorCreateChildFunc -> ActorCreateChildFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ActorCreateChildFunc Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_ActorCreateChildFunc | |
-> a |
|
-> Ptr () |
|
-> m Actor | Returns: The newly created child |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ActorCreateChildFunc :: MonadIO m => ActorCreateChildFunc -> m (GClosure C_ActorCreateChildFunc) Source #
Wrap the callback into a GClosure
.
mk_ActorCreateChildFunc :: C_ActorCreateChildFunc -> IO (FunPtr C_ActorCreateChildFunc) Source #
Generate a function pointer callable from C code, from a C_ActorCreateChildFunc
.
noActorCreateChildFunc :: Maybe ActorCreateChildFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ActorCreateChildFunc
noActorCreateChildFunc_WithClosures :: Maybe ActorCreateChildFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ActorCreateChildFunc_WithClosures
wrap_ActorCreateChildFunc :: Maybe (Ptr (FunPtr C_ActorCreateChildFunc)) -> ActorCreateChildFunc_WithClosures -> C_ActorCreateChildFunc Source #
Wrap a ActorCreateChildFunc
into a C_ActorCreateChildFunc
.
AlphaFunc
Deprecated: (Since version 1.12)Use TimelineProgressFunc
instead.
A function returning a value depending on the position of
the Timeline
bound to alpha
.
Since: 0.2
type AlphaFunc_WithClosures Source #
= Alpha |
|
-> Ptr () |
|
-> IO Double | Returns: a floating point value |
A function returning a value depending on the position of
the Timeline
bound to alpha
.
Since: 0.2
type C_AlphaFunc = Ptr Alpha -> Ptr () -> IO CDouble Source #
Type for the callback on the (unwrapped) C side.
drop_closures_AlphaFunc :: AlphaFunc -> AlphaFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m, IsAlpha a) | |
=> FunPtr C_AlphaFunc | |
-> a |
|
-> Ptr () |
|
-> m Double | Returns: a floating point value |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_AlphaFunc :: MonadIO m => AlphaFunc -> m (GClosure C_AlphaFunc) Source #
Wrap the callback into a GClosure
.
mk_AlphaFunc :: C_AlphaFunc -> IO (FunPtr C_AlphaFunc) Source #
Generate a function pointer callable from C code, from a C_AlphaFunc
.
noAlphaFunc_WithClosures :: Maybe AlphaFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
AlphaFunc_WithClosures
wrap_AlphaFunc :: Maybe (Ptr (FunPtr C_AlphaFunc)) -> AlphaFunc_WithClosures -> C_AlphaFunc Source #
Wrap a AlphaFunc
into a C_AlphaFunc
.
BehaviourForeachFunc
type BehaviourForeachFunc Source #
Deprecated: (Since version 1.6)
This function is passed to behaviourActorsForeach
and
will be called for each actor driven by behaviour
.
Since: 0.2
type BehaviourForeachFunc_WithClosures Source #
= Behaviour |
|
-> Actor |
|
-> Ptr () |
|
-> IO () |
This function is passed to behaviourActorsForeach
and
will be called for each actor driven by behaviour
.
Since: 0.2
type C_BehaviourForeachFunc = Ptr Behaviour -> Ptr Actor -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BehaviourForeachFunc :: BehaviourForeachFunc -> BehaviourForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BehaviourForeachFunc Source #
:: (HasCallStack, MonadIO m, IsBehaviour a, IsActor b) | |
=> FunPtr C_BehaviourForeachFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BehaviourForeachFunc :: MonadIO m => BehaviourForeachFunc -> m (GClosure C_BehaviourForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_BehaviourForeachFunc :: C_BehaviourForeachFunc -> IO (FunPtr C_BehaviourForeachFunc) Source #
Generate a function pointer callable from C code, from a C_BehaviourForeachFunc
.
noBehaviourForeachFunc :: Maybe BehaviourForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
BehaviourForeachFunc
noBehaviourForeachFunc_WithClosures :: Maybe BehaviourForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BehaviourForeachFunc_WithClosures
wrap_BehaviourForeachFunc :: Maybe (Ptr (FunPtr C_BehaviourForeachFunc)) -> BehaviourForeachFunc_WithClosures -> C_BehaviourForeachFunc Source #
Wrap a BehaviourForeachFunc
into a C_BehaviourForeachFunc
.
BindingActionFunc
type BindingActionFunc Source #
= Object |
|
-> Text |
|
-> Word32 |
|
-> [ModifierType] |
|
-> IO Bool | Returns: the function should return |
The prototype for the callback function registered with
bindingPoolInstallAction
and invoked by
bindingPoolActivate
.
Since: 1.0
type BindingActionFunc_WithClosures Source #
= Object |
|
-> Text |
|
-> Word32 |
|
-> [ModifierType] |
|
-> Ptr () |
|
-> IO Bool | Returns: the function should return |
The prototype for the callback function registered with
bindingPoolInstallAction
and invoked by
bindingPoolActivate
.
Since: 1.0
type C_BindingActionFunc = Ptr Object -> CString -> Word32 -> CUInt -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BindingActionFunc :: BindingActionFunc -> BindingActionFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BindingActionFunc Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_BindingActionFunc | |
-> a |
|
-> Text |
|
-> Word32 |
|
-> [ModifierType] |
|
-> Ptr () |
|
-> m Bool | Returns: the function should return |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BindingActionFunc :: MonadIO m => BindingActionFunc -> m (GClosure C_BindingActionFunc) Source #
Wrap the callback into a GClosure
.
mk_BindingActionFunc :: C_BindingActionFunc -> IO (FunPtr C_BindingActionFunc) Source #
Generate a function pointer callable from C code, from a C_BindingActionFunc
.
noBindingActionFunc :: Maybe BindingActionFunc Source #
A convenience synonym for
.Nothing
:: Maybe
BindingActionFunc
noBindingActionFunc_WithClosures :: Maybe BindingActionFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BindingActionFunc_WithClosures
wrap_BindingActionFunc :: Maybe (Ptr (FunPtr C_BindingActionFunc)) -> BindingActionFunc_WithClosures -> C_BindingActionFunc Source #
Wrap a BindingActionFunc
into a C_BindingActionFunc
.
Callback
type C_Callback = Ptr Actor -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type Callback_WithClosures Source #
Generic callback
drop_closures_Callback :: Callback -> Callback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m, IsActor a) | |
=> FunPtr C_Callback | |
-> a |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_Callback :: MonadIO m => Callback -> m (GClosure C_Callback) Source #
Wrap the callback into a GClosure
.
mk_Callback :: C_Callback -> IO (FunPtr C_Callback) Source #
Generate a function pointer callable from C code, from a C_Callback
.
noCallback_WithClosures :: Maybe Callback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
Callback_WithClosures
wrap_Callback :: Maybe (Ptr (FunPtr C_Callback)) -> Callback_WithClosures -> C_Callback Source #
Wrap a Callback
into a C_Callback
.
EventFilterFunc
type C_EventFilterFunc = Ptr Event -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type EventFilterFunc Source #
= Event |
|
-> IO Bool | Returns: |
A function pointer type used by event filters that are added with
eventAddFilter
.
Since: 1.18
type EventFilterFunc_WithClosures Source #
= Event |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function pointer type used by event filters that are added with
eventAddFilter
.
Since: 1.18
drop_closures_EventFilterFunc :: EventFilterFunc -> EventFilterFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_EventFilterFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_EventFilterFunc | |
-> Event |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_EventFilterFunc :: MonadIO m => EventFilterFunc -> m (GClosure C_EventFilterFunc) Source #
Wrap the callback into a GClosure
.
mk_EventFilterFunc :: C_EventFilterFunc -> IO (FunPtr C_EventFilterFunc) Source #
Generate a function pointer callable from C code, from a C_EventFilterFunc
.
noEventFilterFunc :: Maybe EventFilterFunc Source #
A convenience synonym for
.Nothing
:: Maybe
EventFilterFunc
noEventFilterFunc_WithClosures :: Maybe EventFilterFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
EventFilterFunc_WithClosures
wrap_EventFilterFunc :: Maybe (Ptr (FunPtr C_EventFilterFunc)) -> EventFilterFunc_WithClosures -> C_EventFilterFunc Source #
Wrap a EventFilterFunc
into a C_EventFilterFunc
.
ModelFilterFunc
type C_ModelFilterFunc = Ptr Model -> Ptr ModelIter -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ModelFilterFunc Source #
= Model |
|
-> ModelIter |
|
-> IO Bool | Returns: If the row should be displayed, return |
Deprecated: (Since version 1.24)Implement filters using a custom ListModel
instead
Filters the content of a row in the model.
Since: 0.6
type ModelFilterFunc_WithClosures Source #
= Model |
|
-> ModelIter |
|
-> Ptr () |
|
-> IO Bool | Returns: If the row should be displayed, return |
Filters the content of a row in the model.
Since: 0.6
drop_closures_ModelFilterFunc :: ModelFilterFunc -> ModelFilterFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ModelFilterFunc Source #
:: (HasCallStack, MonadIO m, IsModel a, IsModelIter b) | |
=> FunPtr C_ModelFilterFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m Bool | Returns: If the row should be displayed, return |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ModelFilterFunc :: MonadIO m => ModelFilterFunc -> m (GClosure C_ModelFilterFunc) Source #
Wrap the callback into a GClosure
.
mk_ModelFilterFunc :: C_ModelFilterFunc -> IO (FunPtr C_ModelFilterFunc) Source #
Generate a function pointer callable from C code, from a C_ModelFilterFunc
.
noModelFilterFunc :: Maybe ModelFilterFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ModelFilterFunc
noModelFilterFunc_WithClosures :: Maybe ModelFilterFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ModelFilterFunc_WithClosures
wrap_ModelFilterFunc :: Maybe (Ptr (FunPtr C_ModelFilterFunc)) -> ModelFilterFunc_WithClosures -> C_ModelFilterFunc Source #
Wrap a ModelFilterFunc
into a C_ModelFilterFunc
.
ModelForeachFunc
type C_ModelForeachFunc = Ptr Model -> Ptr ModelIter -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ModelForeachFunc Source #
= Model |
|
-> ModelIter |
|
-> IO Bool | Returns: |
Deprecated: (Since version 1.24)Use ListModel
Iterates on the content of a row in the model
Since: 0.6
type ModelForeachFunc_WithClosures Source #
= Model |
|
-> ModelIter |
|
-> Ptr () |
|
-> IO Bool | Returns: |
Iterates on the content of a row in the model
Since: 0.6
drop_closures_ModelForeachFunc :: ModelForeachFunc -> ModelForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ModelForeachFunc Source #
:: (HasCallStack, MonadIO m, IsModel a, IsModelIter b) | |
=> FunPtr C_ModelForeachFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ModelForeachFunc :: MonadIO m => ModelForeachFunc -> m (GClosure C_ModelForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_ModelForeachFunc :: C_ModelForeachFunc -> IO (FunPtr C_ModelForeachFunc) Source #
Generate a function pointer callable from C code, from a C_ModelForeachFunc
.
noModelForeachFunc :: Maybe ModelForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ModelForeachFunc
noModelForeachFunc_WithClosures :: Maybe ModelForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ModelForeachFunc_WithClosures
wrap_ModelForeachFunc :: Maybe (Ptr (FunPtr C_ModelForeachFunc)) -> ModelForeachFunc_WithClosures -> C_ModelForeachFunc Source #
Wrap a ModelForeachFunc
into a C_ModelForeachFunc
.
ModelSortFunc
type C_ModelSortFunc = Ptr Model -> Ptr GValue -> Ptr GValue -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type ModelSortFunc Source #
= Model |
|
-> GValue |
|
-> GValue |
|
-> IO Int32 | Returns: a positive integer if |
Deprecated: (Since version 1.24)Implement sorting using a custom ListModel
instead
Compares the content of two rows in the model.
Since: 0.6
type ModelSortFunc_WithClosures Source #
= Model |
|
-> GValue |
|
-> GValue |
|
-> Ptr () |
|
-> IO Int32 | Returns: a positive integer if |
Compares the content of two rows in the model.
Since: 0.6
drop_closures_ModelSortFunc :: ModelSortFunc -> ModelSortFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ModelSortFunc Source #
:: (HasCallStack, MonadIO m, IsModel a) | |
=> FunPtr C_ModelSortFunc | |
-> a |
|
-> GValue |
|
-> GValue |
|
-> Ptr () |
|
-> m Int32 | Returns: a positive integer if |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ModelSortFunc :: MonadIO m => ModelSortFunc -> m (GClosure C_ModelSortFunc) Source #
Wrap the callback into a GClosure
.
mk_ModelSortFunc :: C_ModelSortFunc -> IO (FunPtr C_ModelSortFunc) Source #
Generate a function pointer callable from C code, from a C_ModelSortFunc
.
noModelSortFunc :: Maybe ModelSortFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ModelSortFunc
noModelSortFunc_WithClosures :: Maybe ModelSortFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ModelSortFunc_WithClosures
wrap_ModelSortFunc :: Maybe (Ptr (FunPtr C_ModelSortFunc)) -> ModelSortFunc_WithClosures -> C_ModelSortFunc Source #
Wrap a ModelSortFunc
into a C_ModelSortFunc
.
PathCallback
type C_PathCallback = Ptr PathNode -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type PathCallback Source #
This function is passed to pathForeach
and will be
called for each node contained in the path.
Since: 1.0
type PathCallback_WithClosures Source #
This function is passed to pathForeach
and will be
called for each node contained in the path.
Since: 1.0
drop_closures_PathCallback :: PathCallback -> PathCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_PathCallback | |
-> PathNode |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PathCallback :: MonadIO m => PathCallback -> m (GClosure C_PathCallback) Source #
Wrap the callback into a GClosure
.
mk_PathCallback :: C_PathCallback -> IO (FunPtr C_PathCallback) Source #
Generate a function pointer callable from C code, from a C_PathCallback
.
noPathCallback :: Maybe PathCallback Source #
A convenience synonym for
.Nothing
:: Maybe
PathCallback
noPathCallback_WithClosures :: Maybe PathCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PathCallback_WithClosures
wrap_PathCallback :: Maybe (Ptr (FunPtr C_PathCallback)) -> PathCallback_WithClosures -> C_PathCallback Source #
Wrap a PathCallback
into a C_PathCallback
.
ProgressFunc
type C_ProgressFunc = Ptr GValue -> Ptr GValue -> CDouble -> Ptr GValue -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ProgressFunc Source #
= GValue |
|
-> GValue |
|
-> Double |
|
-> GValue |
|
-> IO Bool | Returns: |
Prototype of the progress function used to compute the value
between the two ends a
and b
of an interval depending on
the value of progress
.
The Value
in retval
is already initialized with the same
type as a
and b
.
This function will be called by Interval
if the
type of the values of the interval was registered using
clutter_interval_register_progress_func()
.
Since: 1.0
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_ProgressFunc | |
-> GValue |
|
-> GValue |
|
-> Double |
|
-> GValue |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ProgressFunc :: MonadIO m => ProgressFunc -> m (GClosure C_ProgressFunc) Source #
Wrap the callback into a GClosure
.
mk_ProgressFunc :: C_ProgressFunc -> IO (FunPtr C_ProgressFunc) Source #
Generate a function pointer callable from C code, from a C_ProgressFunc
.
noProgressFunc :: Maybe ProgressFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ProgressFunc
wrap_ProgressFunc :: Maybe (Ptr (FunPtr C_ProgressFunc)) -> ProgressFunc -> C_ProgressFunc Source #
Wrap a ProgressFunc
into a C_ProgressFunc
.
ScriptConnectFunc
type C_ScriptConnectFunc = Ptr Script -> Ptr Object -> CString -> CString -> Ptr Object -> CUInt -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ScriptConnectFunc Source #
= Script |
|
-> Object |
|
-> Text |
|
-> Text |
|
-> Object |
|
-> [ConnectFlags] |
|
-> IO () |
This is the signature of a function used to connect signals. It is used
by the scriptConnectSignalsFull
function. It is mainly
intended for interpreted language bindings, but could be useful where the
programmer wants more control over the signal connection process.
Since: 0.6
type ScriptConnectFunc_WithClosures Source #
= Script |
|
-> Object |
|
-> Text |
|
-> Text |
|
-> Object |
|
-> [ConnectFlags] |
|
-> Ptr () |
|
-> IO () |
This is the signature of a function used to connect signals. It is used
by the scriptConnectSignalsFull
function. It is mainly
intended for interpreted language bindings, but could be useful where the
programmer wants more control over the signal connection process.
Since: 0.6
drop_closures_ScriptConnectFunc :: ScriptConnectFunc -> ScriptConnectFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ScriptConnectFunc Source #
:: (HasCallStack, MonadIO m, IsScript a, IsObject b, IsObject c) | |
=> FunPtr C_ScriptConnectFunc | |
-> a |
|
-> b |
|
-> Text |
|
-> Text |
|
-> c |
|
-> [ConnectFlags] |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ScriptConnectFunc :: MonadIO m => ScriptConnectFunc -> m (GClosure C_ScriptConnectFunc) Source #
Wrap the callback into a GClosure
.
mk_ScriptConnectFunc :: C_ScriptConnectFunc -> IO (FunPtr C_ScriptConnectFunc) Source #
Generate a function pointer callable from C code, from a C_ScriptConnectFunc
.
noScriptConnectFunc :: Maybe ScriptConnectFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ScriptConnectFunc
noScriptConnectFunc_WithClosures :: Maybe ScriptConnectFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ScriptConnectFunc_WithClosures
wrap_ScriptConnectFunc :: Maybe (Ptr (FunPtr C_ScriptConnectFunc)) -> ScriptConnectFunc_WithClosures -> C_ScriptConnectFunc Source #
Wrap a ScriptConnectFunc
into a C_ScriptConnectFunc
.
TimelineProgressFunc
type C_TimelineProgressFunc = Ptr Timeline -> CDouble -> CDouble -> Ptr () -> IO CDouble Source #
Type for the callback on the (unwrapped) C side.
type TimelineProgressFunc Source #
= Timeline |
|
-> Double |
|
-> Double |
|
-> IO Double | Returns: the progress, as a floating point value between -1.0 and 2.0. |
A function for defining a custom progress.
Since: 1.10
type TimelineProgressFunc_WithClosures Source #
= Timeline |
|
-> Double |
|
-> Double |
|
-> Ptr () |
|
-> IO Double | Returns: the progress, as a floating point value between -1.0 and 2.0. |
A function for defining a custom progress.
Since: 1.10
drop_closures_TimelineProgressFunc :: TimelineProgressFunc -> TimelineProgressFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TimelineProgressFunc Source #
:: (HasCallStack, MonadIO m, IsTimeline a) | |
=> FunPtr C_TimelineProgressFunc | |
-> a |
|
-> Double |
|
-> Double |
|
-> Ptr () |
|
-> m Double | Returns: the progress, as a floating point value between -1.0 and 2.0. |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TimelineProgressFunc :: MonadIO m => TimelineProgressFunc -> m (GClosure C_TimelineProgressFunc) Source #
Wrap the callback into a GClosure
.
mk_TimelineProgressFunc :: C_TimelineProgressFunc -> IO (FunPtr C_TimelineProgressFunc) Source #
Generate a function pointer callable from C code, from a C_TimelineProgressFunc
.
noTimelineProgressFunc :: Maybe TimelineProgressFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TimelineProgressFunc
noTimelineProgressFunc_WithClosures :: Maybe TimelineProgressFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TimelineProgressFunc_WithClosures