| 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 | 
GI.GLib.Callbacks
Contents
- Signals- ChildWatchFunc
- ClearHandleFunc
- CompareDataFunc
- CompareFunc
- CopyFunc
- DataForeachFunc
- DestroyNotify
- DuplicateFunc
- EqualFunc
- FreeFunc
- Func
- HFunc
- HRFunc
- HashFunc
- HookCheckFunc
- HookCheckMarshaller
- HookCompareFunc
- HookFinalizeFunc
- HookFindFunc
- HookFunc
- HookMarshaller
- IOFunc
- IOFuncsIoCloseFieldCallback
- IOFuncsIoCreateWatchFieldCallback
- IOFuncsIoFreeFieldCallback
- IOFuncsIoGetFlagsFieldCallback
- IOFuncsIoReadFieldCallback
- IOFuncsIoSeekFieldCallback
- IOFuncsIoSetFlagsFieldCallback
- IOFuncsIoWriteFieldCallback
- LogFunc
- LogWriterFunc
- MarkupParserEndElementFieldCallback
- MarkupParserErrorFieldCallback
- MarkupParserPassthroughFieldCallback
- MarkupParserStartElementFieldCallback
- MarkupParserTextFieldCallback
- MemVTableCallocFieldCallback
- MemVTableFreeFieldCallback
- MemVTableMallocFieldCallback
- MemVTableReallocFieldCallback
- MemVTableTryMallocFieldCallback
- MemVTableTryReallocFieldCallback
- NodeForeachFunc
- NodeTraverseFunc
- OptionArgFunc
- OptionErrorFunc
- OptionParseFunc
- PollFunc
- PrintFunc
- RegexEvalCallback
- ScannerMsgFunc
- SequenceIterCompareFunc
- SourceCallbackFuncsRefFieldCallback
- SourceCallbackFuncsUnrefFieldCallback
- SourceDummyMarshal
- SourceFunc
- SourceFuncsCheckFieldCallback
- SourceFuncsFinalizeFieldCallback
- SourceFuncsPrepareFieldCallback
- SpawnChildSetupFunc
- TestDataFunc
- TestFixtureFunc
- TestFunc
- TestLogFatalFunc
- ThreadFunc
- TranslateFunc
- TraverseFunc
- UnixFDSourceFunc
- VoidFunc
 
Description
Synopsis
- type C_ChildWatchFunc = Int32 -> Int32 -> Ptr () -> IO ()
- type ChildWatchFunc = Int32 -> Int32 -> IO ()
- type ChildWatchFunc_WithClosures = Int32 -> Int32 -> Ptr () -> IO ()
- drop_closures_ChildWatchFunc :: ChildWatchFunc -> ChildWatchFunc_WithClosures
- dynamic_ChildWatchFunc :: (HasCallStack, MonadIO m) => FunPtr C_ChildWatchFunc -> Int32 -> Int32 -> Ptr () -> m ()
- genClosure_ChildWatchFunc :: MonadIO m => ChildWatchFunc -> m (GClosure C_ChildWatchFunc)
- mk_ChildWatchFunc :: C_ChildWatchFunc -> IO (FunPtr C_ChildWatchFunc)
- noChildWatchFunc :: Maybe ChildWatchFunc
- noChildWatchFunc_WithClosures :: Maybe ChildWatchFunc_WithClosures
- wrap_ChildWatchFunc :: Maybe (Ptr (FunPtr C_ChildWatchFunc)) -> ChildWatchFunc_WithClosures -> C_ChildWatchFunc
- type C_ClearHandleFunc = Word32 -> IO ()
- type ClearHandleFunc = Word32 -> IO ()
- dynamic_ClearHandleFunc :: (HasCallStack, MonadIO m) => FunPtr C_ClearHandleFunc -> Word32 -> m ()
- genClosure_ClearHandleFunc :: MonadIO m => ClearHandleFunc -> m (GClosure C_ClearHandleFunc)
- mk_ClearHandleFunc :: C_ClearHandleFunc -> IO (FunPtr C_ClearHandleFunc)
- noClearHandleFunc :: Maybe ClearHandleFunc
- wrap_ClearHandleFunc :: Maybe (Ptr (FunPtr C_ClearHandleFunc)) -> ClearHandleFunc -> C_ClearHandleFunc
- type C_CompareDataFunc = Ptr () -> Ptr () -> Ptr () -> IO Int32
- type CompareDataFunc = Ptr () -> Ptr () -> IO Int32
- type CompareDataFunc_WithClosures = Ptr () -> Ptr () -> Ptr () -> IO Int32
- drop_closures_CompareDataFunc :: CompareDataFunc -> CompareDataFunc_WithClosures
- dynamic_CompareDataFunc :: (HasCallStack, MonadIO m) => FunPtr C_CompareDataFunc -> Ptr () -> Ptr () -> Ptr () -> m Int32
- genClosure_CompareDataFunc :: MonadIO m => CompareDataFunc -> m (GClosure C_CompareDataFunc)
- mk_CompareDataFunc :: C_CompareDataFunc -> IO (FunPtr C_CompareDataFunc)
- noCompareDataFunc :: Maybe CompareDataFunc
- noCompareDataFunc_WithClosures :: Maybe CompareDataFunc_WithClosures
- wrap_CompareDataFunc :: Maybe (Ptr (FunPtr C_CompareDataFunc)) -> CompareDataFunc_WithClosures -> C_CompareDataFunc
- type C_CompareFunc = Ptr () -> Ptr () -> IO Int32
- type CompareFunc = Ptr () -> Ptr () -> IO Int32
- dynamic_CompareFunc :: (HasCallStack, MonadIO m) => FunPtr C_CompareFunc -> Ptr () -> Ptr () -> m Int32
- genClosure_CompareFunc :: MonadIO m => CompareFunc -> m (GClosure C_CompareFunc)
- mk_CompareFunc :: C_CompareFunc -> IO (FunPtr C_CompareFunc)
- noCompareFunc :: Maybe CompareFunc
- wrap_CompareFunc :: Maybe (Ptr (FunPtr C_CompareFunc)) -> CompareFunc -> C_CompareFunc
- type C_CopyFunc = Ptr () -> Ptr () -> IO (Ptr ())
- type CopyFunc = Ptr () -> Ptr () -> IO (Ptr ())
- dynamic_CopyFunc :: (HasCallStack, MonadIO m) => FunPtr C_CopyFunc -> Ptr () -> Ptr () -> m (Ptr ())
- genClosure_CopyFunc :: MonadIO m => CopyFunc -> m (GClosure C_CopyFunc)
- mk_CopyFunc :: C_CopyFunc -> IO (FunPtr C_CopyFunc)
- noCopyFunc :: Maybe CopyFunc
- wrap_CopyFunc :: Maybe (Ptr (FunPtr C_CopyFunc)) -> CopyFunc -> C_CopyFunc
- type C_DataForeachFunc = Word32 -> Ptr () -> Ptr () -> IO ()
- type DataForeachFunc = Word32 -> Ptr () -> IO ()
- type DataForeachFunc_WithClosures = Word32 -> Ptr () -> Ptr () -> IO ()
- drop_closures_DataForeachFunc :: DataForeachFunc -> DataForeachFunc_WithClosures
- dynamic_DataForeachFunc :: (HasCallStack, MonadIO m) => FunPtr C_DataForeachFunc -> Word32 -> Ptr () -> Ptr () -> m ()
- genClosure_DataForeachFunc :: MonadIO m => DataForeachFunc -> m (GClosure C_DataForeachFunc)
- mk_DataForeachFunc :: C_DataForeachFunc -> IO (FunPtr C_DataForeachFunc)
- noDataForeachFunc :: Maybe DataForeachFunc
- noDataForeachFunc_WithClosures :: Maybe DataForeachFunc_WithClosures
- wrap_DataForeachFunc :: Maybe (Ptr (FunPtr C_DataForeachFunc)) -> DataForeachFunc_WithClosures -> C_DataForeachFunc
- type C_DestroyNotify = Ptr () -> IO ()
- type DestroyNotify = Ptr () -> IO ()
- dynamic_DestroyNotify :: (HasCallStack, MonadIO m) => FunPtr C_DestroyNotify -> Ptr () -> m ()
- genClosure_DestroyNotify :: MonadIO m => DestroyNotify -> m (GClosure C_DestroyNotify)
- mk_DestroyNotify :: C_DestroyNotify -> IO (FunPtr C_DestroyNotify)
- noDestroyNotify :: Maybe DestroyNotify
- wrap_DestroyNotify :: Maybe (Ptr (FunPtr C_DestroyNotify)) -> DestroyNotify -> C_DestroyNotify
- type C_DuplicateFunc = Ptr () -> Ptr () -> IO (Ptr ())
- type DuplicateFunc = Ptr () -> IO (Ptr ())
- type DuplicateFunc_WithClosures = Ptr () -> Ptr () -> IO (Ptr ())
- drop_closures_DuplicateFunc :: DuplicateFunc -> DuplicateFunc_WithClosures
- dynamic_DuplicateFunc :: (HasCallStack, MonadIO m) => FunPtr C_DuplicateFunc -> Ptr () -> Ptr () -> m (Ptr ())
- genClosure_DuplicateFunc :: MonadIO m => DuplicateFunc -> m (GClosure C_DuplicateFunc)
- mk_DuplicateFunc :: C_DuplicateFunc -> IO (FunPtr C_DuplicateFunc)
- noDuplicateFunc :: Maybe DuplicateFunc
- noDuplicateFunc_WithClosures :: Maybe DuplicateFunc_WithClosures
- wrap_DuplicateFunc :: Maybe (Ptr (FunPtr C_DuplicateFunc)) -> DuplicateFunc_WithClosures -> C_DuplicateFunc
- type C_EqualFunc = Ptr () -> Ptr () -> IO CInt
- type EqualFunc = Ptr () -> Ptr () -> IO Bool
- dynamic_EqualFunc :: (HasCallStack, MonadIO m) => FunPtr C_EqualFunc -> Ptr () -> Ptr () -> m Bool
- genClosure_EqualFunc :: MonadIO m => EqualFunc -> m (GClosure C_EqualFunc)
- mk_EqualFunc :: C_EqualFunc -> IO (FunPtr C_EqualFunc)
- noEqualFunc :: Maybe EqualFunc
- wrap_EqualFunc :: Maybe (Ptr (FunPtr C_EqualFunc)) -> EqualFunc -> C_EqualFunc
- type C_FreeFunc = Ptr () -> IO ()
- type FreeFunc = Ptr () -> IO ()
- dynamic_FreeFunc :: (HasCallStack, MonadIO m) => FunPtr C_FreeFunc -> Ptr () -> m ()
- genClosure_FreeFunc :: MonadIO m => FreeFunc -> m (GClosure C_FreeFunc)
- mk_FreeFunc :: C_FreeFunc -> IO (FunPtr C_FreeFunc)
- noFreeFunc :: Maybe FreeFunc
- wrap_FreeFunc :: Maybe (Ptr (FunPtr C_FreeFunc)) -> FreeFunc -> C_FreeFunc
- type C_Func = Ptr () -> Ptr () -> IO ()
- type Func = Ptr () -> IO ()
- type Func_WithClosures = Ptr () -> Ptr () -> IO ()
- drop_closures_Func :: Func -> Func_WithClosures
- dynamic_Func :: (HasCallStack, MonadIO m) => FunPtr C_Func -> Ptr () -> Ptr () -> m ()
- genClosure_Func :: MonadIO m => Func -> m (GClosure C_Func)
- mk_Func :: C_Func -> IO (FunPtr C_Func)
- noFunc :: Maybe Func
- noFunc_WithClosures :: Maybe Func_WithClosures
- wrap_Func :: Maybe (Ptr (FunPtr C_Func)) -> Func_WithClosures -> C_Func
- type C_HFunc = Ptr () -> Ptr () -> Ptr () -> IO ()
- type HFunc = Ptr () -> Ptr () -> IO ()
- type HFunc_WithClosures = Ptr () -> Ptr () -> Ptr () -> IO ()
- drop_closures_HFunc :: HFunc -> HFunc_WithClosures
- dynamic_HFunc :: (HasCallStack, MonadIO m) => FunPtr C_HFunc -> Ptr () -> Ptr () -> Ptr () -> m ()
- genClosure_HFunc :: MonadIO m => HFunc -> m (GClosure C_HFunc)
- mk_HFunc :: C_HFunc -> IO (FunPtr C_HFunc)
- noHFunc :: Maybe HFunc
- noHFunc_WithClosures :: Maybe HFunc_WithClosures
- wrap_HFunc :: Maybe (Ptr (FunPtr C_HFunc)) -> HFunc_WithClosures -> C_HFunc
- type C_HRFunc = Ptr () -> Ptr () -> Ptr () -> IO CInt
- type HRFunc = Ptr () -> Ptr () -> IO Bool
- type HRFunc_WithClosures = Ptr () -> Ptr () -> Ptr () -> IO Bool
- drop_closures_HRFunc :: HRFunc -> HRFunc_WithClosures
- dynamic_HRFunc :: (HasCallStack, MonadIO m) => FunPtr C_HRFunc -> Ptr () -> Ptr () -> Ptr () -> m Bool
- genClosure_HRFunc :: MonadIO m => HRFunc -> m (GClosure C_HRFunc)
- mk_HRFunc :: C_HRFunc -> IO (FunPtr C_HRFunc)
- noHRFunc :: Maybe HRFunc
- noHRFunc_WithClosures :: Maybe HRFunc_WithClosures
- wrap_HRFunc :: Maybe (Ptr (FunPtr C_HRFunc)) -> HRFunc_WithClosures -> C_HRFunc
- type C_HashFunc = Ptr () -> IO Word32
- type HashFunc = Ptr () -> IO Word32
- dynamic_HashFunc :: (HasCallStack, MonadIO m) => FunPtr C_HashFunc -> Ptr () -> m Word32
- genClosure_HashFunc :: MonadIO m => HashFunc -> m (GClosure C_HashFunc)
- mk_HashFunc :: C_HashFunc -> IO (FunPtr C_HashFunc)
- noHashFunc :: Maybe HashFunc
- wrap_HashFunc :: Maybe (Ptr (FunPtr C_HashFunc)) -> HashFunc -> C_HashFunc
- type C_HookCheckFunc = Ptr () -> IO CInt
- type HookCheckFunc = Ptr () -> IO Bool
- dynamic_HookCheckFunc :: (HasCallStack, MonadIO m) => FunPtr C_HookCheckFunc -> Ptr () -> m Bool
- genClosure_HookCheckFunc :: MonadIO m => HookCheckFunc -> m (GClosure C_HookCheckFunc)
- mk_HookCheckFunc :: C_HookCheckFunc -> IO (FunPtr C_HookCheckFunc)
- noHookCheckFunc :: Maybe HookCheckFunc
- wrap_HookCheckFunc :: Maybe (Ptr (FunPtr C_HookCheckFunc)) -> HookCheckFunc -> C_HookCheckFunc
- type C_HookCheckMarshaller = Ptr Hook -> Ptr () -> IO CInt
- type HookCheckMarshaller = Hook -> Ptr () -> IO Bool
- dynamic_HookCheckMarshaller :: (HasCallStack, MonadIO m) => FunPtr C_HookCheckMarshaller -> Hook -> Ptr () -> m Bool
- genClosure_HookCheckMarshaller :: MonadIO m => HookCheckMarshaller -> m (GClosure C_HookCheckMarshaller)
- mk_HookCheckMarshaller :: C_HookCheckMarshaller -> IO (FunPtr C_HookCheckMarshaller)
- noHookCheckMarshaller :: Maybe HookCheckMarshaller
- wrap_HookCheckMarshaller :: Maybe (Ptr (FunPtr C_HookCheckMarshaller)) -> HookCheckMarshaller -> C_HookCheckMarshaller
- type C_HookCompareFunc = Ptr Hook -> Ptr Hook -> IO Int32
- type HookCompareFunc = Hook -> Hook -> IO Int32
- dynamic_HookCompareFunc :: (HasCallStack, MonadIO m) => FunPtr C_HookCompareFunc -> Hook -> Hook -> m Int32
- genClosure_HookCompareFunc :: MonadIO m => HookCompareFunc -> m (GClosure C_HookCompareFunc)
- mk_HookCompareFunc :: C_HookCompareFunc -> IO (FunPtr C_HookCompareFunc)
- noHookCompareFunc :: Maybe HookCompareFunc
- wrap_HookCompareFunc :: Maybe (Ptr (FunPtr C_HookCompareFunc)) -> HookCompareFunc -> C_HookCompareFunc
- type C_HookFinalizeFunc = Ptr HookList -> Ptr Hook -> IO ()
- type HookFinalizeFunc = HookList -> Hook -> IO ()
- dynamic_HookFinalizeFunc :: (HasCallStack, MonadIO m) => FunPtr C_HookFinalizeFunc -> HookList -> Hook -> m ()
- genClosure_HookFinalizeFunc :: MonadIO m => HookFinalizeFunc -> m (GClosure C_HookFinalizeFunc)
- mk_HookFinalizeFunc :: C_HookFinalizeFunc -> IO (FunPtr C_HookFinalizeFunc)
- noHookFinalizeFunc :: Maybe HookFinalizeFunc
- wrap_HookFinalizeFunc :: Maybe (Ptr (FunPtr C_HookFinalizeFunc)) -> HookFinalizeFunc -> C_HookFinalizeFunc
- type C_HookFindFunc = Ptr Hook -> Ptr () -> IO CInt
- type HookFindFunc = Hook -> Ptr () -> IO Bool
- dynamic_HookFindFunc :: (HasCallStack, MonadIO m) => FunPtr C_HookFindFunc -> Hook -> Ptr () -> m Bool
- genClosure_HookFindFunc :: MonadIO m => HookFindFunc -> m (GClosure C_HookFindFunc)
- mk_HookFindFunc :: C_HookFindFunc -> IO (FunPtr C_HookFindFunc)
- noHookFindFunc :: Maybe HookFindFunc
- wrap_HookFindFunc :: Maybe (Ptr (FunPtr C_HookFindFunc)) -> HookFindFunc -> C_HookFindFunc
- type C_HookFunc = Ptr () -> IO ()
- type HookFunc = Ptr () -> IO ()
- dynamic_HookFunc :: (HasCallStack, MonadIO m) => FunPtr C_HookFunc -> Ptr () -> m ()
- genClosure_HookFunc :: MonadIO m => HookFunc -> m (GClosure C_HookFunc)
- mk_HookFunc :: C_HookFunc -> IO (FunPtr C_HookFunc)
- noHookFunc :: Maybe HookFunc
- wrap_HookFunc :: Maybe (Ptr (FunPtr C_HookFunc)) -> HookFunc -> C_HookFunc
- type C_HookMarshaller = Ptr Hook -> Ptr () -> IO ()
- type HookMarshaller = Hook -> Ptr () -> IO ()
- dynamic_HookMarshaller :: (HasCallStack, MonadIO m) => FunPtr C_HookMarshaller -> Hook -> Ptr () -> m ()
- genClosure_HookMarshaller :: MonadIO m => HookMarshaller -> m (GClosure C_HookMarshaller)
- mk_HookMarshaller :: C_HookMarshaller -> IO (FunPtr C_HookMarshaller)
- noHookMarshaller :: Maybe HookMarshaller
- wrap_HookMarshaller :: Maybe (Ptr (FunPtr C_HookMarshaller)) -> HookMarshaller -> C_HookMarshaller
- type C_IOFunc = Ptr IOChannel -> CUInt -> Ptr () -> IO CInt
- type IOFunc = IOChannel -> [IOCondition] -> Ptr () -> IO Bool
- dynamic_IOFunc :: (HasCallStack, MonadIO m) => FunPtr C_IOFunc -> IOChannel -> [IOCondition] -> Ptr () -> m Bool
- genClosure_IOFunc :: MonadIO m => IOFunc -> m (GClosure C_IOFunc)
- mk_IOFunc :: C_IOFunc -> IO (FunPtr C_IOFunc)
- noIOFunc :: Maybe IOFunc
- wrap_IOFunc :: Maybe (Ptr (FunPtr C_IOFunc)) -> IOFunc -> C_IOFunc
- type C_IOFuncsIoCloseFieldCallback = Ptr IOChannel -> Ptr (Ptr GError) -> IO CUInt
- type IOFuncsIoCloseFieldCallback = IOChannel -> IO IOStatus
- dynamic_IOFuncsIoCloseFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoCloseFieldCallback -> IOChannel -> m IOStatus
- mk_IOFuncsIoCloseFieldCallback :: C_IOFuncsIoCloseFieldCallback -> IO (FunPtr C_IOFuncsIoCloseFieldCallback)
- noIOFuncsIoCloseFieldCallback :: Maybe IOFuncsIoCloseFieldCallback
- type C_IOFuncsIoCreateWatchFieldCallback = Ptr IOChannel -> CUInt -> IO (Ptr Source)
- type IOFuncsIoCreateWatchFieldCallback = IOChannel -> [IOCondition] -> IO Source
- dynamic_IOFuncsIoCreateWatchFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoCreateWatchFieldCallback -> IOChannel -> [IOCondition] -> m Source
- genClosure_IOFuncsIoCreateWatchFieldCallback :: MonadIO m => IOFuncsIoCreateWatchFieldCallback -> m (GClosure C_IOFuncsIoCreateWatchFieldCallback)
- mk_IOFuncsIoCreateWatchFieldCallback :: C_IOFuncsIoCreateWatchFieldCallback -> IO (FunPtr C_IOFuncsIoCreateWatchFieldCallback)
- noIOFuncsIoCreateWatchFieldCallback :: Maybe IOFuncsIoCreateWatchFieldCallback
- wrap_IOFuncsIoCreateWatchFieldCallback :: Maybe (Ptr (FunPtr C_IOFuncsIoCreateWatchFieldCallback)) -> IOFuncsIoCreateWatchFieldCallback -> C_IOFuncsIoCreateWatchFieldCallback
- type C_IOFuncsIoFreeFieldCallback = Ptr IOChannel -> IO ()
- type IOFuncsIoFreeFieldCallback = IOChannel -> IO ()
- dynamic_IOFuncsIoFreeFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoFreeFieldCallback -> IOChannel -> m ()
- genClosure_IOFuncsIoFreeFieldCallback :: MonadIO m => IOFuncsIoFreeFieldCallback -> m (GClosure C_IOFuncsIoFreeFieldCallback)
- mk_IOFuncsIoFreeFieldCallback :: C_IOFuncsIoFreeFieldCallback -> IO (FunPtr C_IOFuncsIoFreeFieldCallback)
- noIOFuncsIoFreeFieldCallback :: Maybe IOFuncsIoFreeFieldCallback
- wrap_IOFuncsIoFreeFieldCallback :: Maybe (Ptr (FunPtr C_IOFuncsIoFreeFieldCallback)) -> IOFuncsIoFreeFieldCallback -> C_IOFuncsIoFreeFieldCallback
- type C_IOFuncsIoGetFlagsFieldCallback = Ptr IOChannel -> IO CUInt
- type IOFuncsIoGetFlagsFieldCallback = IOChannel -> IO [IOFlags]
- dynamic_IOFuncsIoGetFlagsFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoGetFlagsFieldCallback -> IOChannel -> m [IOFlags]
- genClosure_IOFuncsIoGetFlagsFieldCallback :: MonadIO m => IOFuncsIoGetFlagsFieldCallback -> m (GClosure C_IOFuncsIoGetFlagsFieldCallback)
- mk_IOFuncsIoGetFlagsFieldCallback :: C_IOFuncsIoGetFlagsFieldCallback -> IO (FunPtr C_IOFuncsIoGetFlagsFieldCallback)
- noIOFuncsIoGetFlagsFieldCallback :: Maybe IOFuncsIoGetFlagsFieldCallback
- wrap_IOFuncsIoGetFlagsFieldCallback :: Maybe (Ptr (FunPtr C_IOFuncsIoGetFlagsFieldCallback)) -> IOFuncsIoGetFlagsFieldCallback -> C_IOFuncsIoGetFlagsFieldCallback
- type C_IOFuncsIoReadFieldCallback = Ptr IOChannel -> CString -> Word64 -> Word64 -> Ptr (Ptr GError) -> IO CUInt
- type IOFuncsIoReadFieldCallback = IOChannel -> Text -> Word64 -> Word64 -> IO IOStatus
- dynamic_IOFuncsIoReadFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoReadFieldCallback -> IOChannel -> Text -> Word64 -> Word64 -> m IOStatus
- mk_IOFuncsIoReadFieldCallback :: C_IOFuncsIoReadFieldCallback -> IO (FunPtr C_IOFuncsIoReadFieldCallback)
- noIOFuncsIoReadFieldCallback :: Maybe IOFuncsIoReadFieldCallback
- type C_IOFuncsIoSeekFieldCallback = Ptr IOChannel -> Int64 -> CUInt -> Ptr (Ptr GError) -> IO CUInt
- type IOFuncsIoSeekFieldCallback = IOChannel -> Int64 -> SeekType -> IO IOStatus
- dynamic_IOFuncsIoSeekFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoSeekFieldCallback -> IOChannel -> Int64 -> SeekType -> m IOStatus
- mk_IOFuncsIoSeekFieldCallback :: C_IOFuncsIoSeekFieldCallback -> IO (FunPtr C_IOFuncsIoSeekFieldCallback)
- noIOFuncsIoSeekFieldCallback :: Maybe IOFuncsIoSeekFieldCallback
- type C_IOFuncsIoSetFlagsFieldCallback = Ptr IOChannel -> CUInt -> Ptr (Ptr GError) -> IO CUInt
- type IOFuncsIoSetFlagsFieldCallback = IOChannel -> [IOFlags] -> IO IOStatus
- dynamic_IOFuncsIoSetFlagsFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoSetFlagsFieldCallback -> IOChannel -> [IOFlags] -> m IOStatus
- mk_IOFuncsIoSetFlagsFieldCallback :: C_IOFuncsIoSetFlagsFieldCallback -> IO (FunPtr C_IOFuncsIoSetFlagsFieldCallback)
- noIOFuncsIoSetFlagsFieldCallback :: Maybe IOFuncsIoSetFlagsFieldCallback
- type C_IOFuncsIoWriteFieldCallback = Ptr IOChannel -> CString -> Word64 -> Word64 -> Ptr (Ptr GError) -> IO CUInt
- type IOFuncsIoWriteFieldCallback = IOChannel -> Text -> Word64 -> Word64 -> IO IOStatus
- dynamic_IOFuncsIoWriteFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoWriteFieldCallback -> IOChannel -> Text -> Word64 -> Word64 -> m IOStatus
- mk_IOFuncsIoWriteFieldCallback :: C_IOFuncsIoWriteFieldCallback -> IO (FunPtr C_IOFuncsIoWriteFieldCallback)
- noIOFuncsIoWriteFieldCallback :: Maybe IOFuncsIoWriteFieldCallback
- type C_LogFunc = CString -> CInt -> CString -> Ptr () -> IO ()
- type LogFunc = Text -> [LogLevelFlags] -> Text -> IO ()
- type LogFunc_WithClosures = Text -> [LogLevelFlags] -> Text -> Ptr () -> IO ()
- drop_closures_LogFunc :: LogFunc -> LogFunc_WithClosures
- dynamic_LogFunc :: (HasCallStack, MonadIO m) => FunPtr C_LogFunc -> Text -> [LogLevelFlags] -> Text -> Ptr () -> m ()
- genClosure_LogFunc :: MonadIO m => LogFunc -> m (GClosure C_LogFunc)
- mk_LogFunc :: C_LogFunc -> IO (FunPtr C_LogFunc)
- noLogFunc :: Maybe LogFunc
- noLogFunc_WithClosures :: Maybe LogFunc_WithClosures
- wrap_LogFunc :: Maybe (Ptr (FunPtr C_LogFunc)) -> LogFunc_WithClosures -> C_LogFunc
- type C_LogWriterFunc = CInt -> Ptr LogField -> Word64 -> Ptr () -> IO CUInt
- type LogWriterFunc = [LogLevelFlags] -> [LogField] -> IO LogWriterOutput
- type LogWriterFunc_WithClosures = [LogLevelFlags] -> [LogField] -> Ptr () -> IO LogWriterOutput
- drop_closures_LogWriterFunc :: LogWriterFunc -> LogWriterFunc_WithClosures
- dynamic_LogWriterFunc :: (HasCallStack, MonadIO m) => FunPtr C_LogWriterFunc -> [LogLevelFlags] -> [LogField] -> Ptr () -> m LogWriterOutput
- genClosure_LogWriterFunc :: MonadIO m => LogWriterFunc -> m (GClosure C_LogWriterFunc)
- mk_LogWriterFunc :: C_LogWriterFunc -> IO (FunPtr C_LogWriterFunc)
- noLogWriterFunc :: Maybe LogWriterFunc
- noLogWriterFunc_WithClosures :: Maybe LogWriterFunc_WithClosures
- wrap_LogWriterFunc :: Maybe (Ptr (FunPtr C_LogWriterFunc)) -> LogWriterFunc_WithClosures -> C_LogWriterFunc
- type C_MarkupParserEndElementFieldCallback = Ptr MarkupParseContext -> CString -> Ptr () -> Ptr (Ptr GError) -> IO ()
- type MarkupParserEndElementFieldCallback = MarkupParseContext -> Text -> IO ()
- type MarkupParserEndElementFieldCallback_WithClosures = MarkupParseContext -> Text -> Ptr () -> IO ()
- drop_closures_MarkupParserEndElementFieldCallback :: MarkupParserEndElementFieldCallback -> MarkupParserEndElementFieldCallback_WithClosures
- dynamic_MarkupParserEndElementFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MarkupParserEndElementFieldCallback -> MarkupParseContext -> Text -> Ptr () -> m ()
- mk_MarkupParserEndElementFieldCallback :: C_MarkupParserEndElementFieldCallback -> IO (FunPtr C_MarkupParserEndElementFieldCallback)
- noMarkupParserEndElementFieldCallback :: Maybe MarkupParserEndElementFieldCallback
- noMarkupParserEndElementFieldCallback_WithClosures :: Maybe MarkupParserEndElementFieldCallback_WithClosures
- type C_MarkupParserErrorFieldCallback = Ptr MarkupParseContext -> Ptr GError -> Ptr () -> IO ()
- type MarkupParserErrorFieldCallback = MarkupParseContext -> GError -> IO ()
- type MarkupParserErrorFieldCallback_WithClosures = MarkupParseContext -> GError -> Ptr () -> IO ()
- drop_closures_MarkupParserErrorFieldCallback :: MarkupParserErrorFieldCallback -> MarkupParserErrorFieldCallback_WithClosures
- dynamic_MarkupParserErrorFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MarkupParserErrorFieldCallback -> MarkupParseContext -> GError -> Ptr () -> m ()
- genClosure_MarkupParserErrorFieldCallback :: MonadIO m => MarkupParserErrorFieldCallback -> m (GClosure C_MarkupParserErrorFieldCallback)
- mk_MarkupParserErrorFieldCallback :: C_MarkupParserErrorFieldCallback -> IO (FunPtr C_MarkupParserErrorFieldCallback)
- noMarkupParserErrorFieldCallback :: Maybe MarkupParserErrorFieldCallback
- noMarkupParserErrorFieldCallback_WithClosures :: Maybe MarkupParserErrorFieldCallback_WithClosures
- wrap_MarkupParserErrorFieldCallback :: Maybe (Ptr (FunPtr C_MarkupParserErrorFieldCallback)) -> MarkupParserErrorFieldCallback_WithClosures -> C_MarkupParserErrorFieldCallback
- type C_MarkupParserPassthroughFieldCallback = Ptr MarkupParseContext -> CString -> Word64 -> Ptr () -> Ptr (Ptr GError) -> IO ()
- type MarkupParserPassthroughFieldCallback = MarkupParseContext -> Text -> Word64 -> IO ()
- type MarkupParserPassthroughFieldCallback_WithClosures = MarkupParseContext -> Text -> Word64 -> Ptr () -> IO ()
- drop_closures_MarkupParserPassthroughFieldCallback :: MarkupParserPassthroughFieldCallback -> MarkupParserPassthroughFieldCallback_WithClosures
- dynamic_MarkupParserPassthroughFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MarkupParserPassthroughFieldCallback -> MarkupParseContext -> Text -> Word64 -> Ptr () -> m ()
- mk_MarkupParserPassthroughFieldCallback :: C_MarkupParserPassthroughFieldCallback -> IO (FunPtr C_MarkupParserPassthroughFieldCallback)
- noMarkupParserPassthroughFieldCallback :: Maybe MarkupParserPassthroughFieldCallback
- noMarkupParserPassthroughFieldCallback_WithClosures :: Maybe MarkupParserPassthroughFieldCallback_WithClosures
- type C_MarkupParserStartElementFieldCallback = Ptr MarkupParseContext -> CString -> CString -> CString -> Ptr () -> Ptr (Ptr GError) -> IO ()
- type MarkupParserStartElementFieldCallback = MarkupParseContext -> Text -> Text -> Text -> IO ()
- type MarkupParserStartElementFieldCallback_WithClosures = MarkupParseContext -> Text -> Text -> Text -> Ptr () -> IO ()
- drop_closures_MarkupParserStartElementFieldCallback :: MarkupParserStartElementFieldCallback -> MarkupParserStartElementFieldCallback_WithClosures
- dynamic_MarkupParserStartElementFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MarkupParserStartElementFieldCallback -> MarkupParseContext -> Text -> Text -> Text -> Ptr () -> m ()
- mk_MarkupParserStartElementFieldCallback :: C_MarkupParserStartElementFieldCallback -> IO (FunPtr C_MarkupParserStartElementFieldCallback)
- noMarkupParserStartElementFieldCallback :: Maybe MarkupParserStartElementFieldCallback
- noMarkupParserStartElementFieldCallback_WithClosures :: Maybe MarkupParserStartElementFieldCallback_WithClosures
- type C_MarkupParserTextFieldCallback = Ptr MarkupParseContext -> CString -> Word64 -> Ptr () -> Ptr (Ptr GError) -> IO ()
- type MarkupParserTextFieldCallback = MarkupParseContext -> Text -> Word64 -> IO ()
- type MarkupParserTextFieldCallback_WithClosures = MarkupParseContext -> Text -> Word64 -> Ptr () -> IO ()
- drop_closures_MarkupParserTextFieldCallback :: MarkupParserTextFieldCallback -> MarkupParserTextFieldCallback_WithClosures
- dynamic_MarkupParserTextFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MarkupParserTextFieldCallback -> MarkupParseContext -> Text -> Word64 -> Ptr () -> m ()
- mk_MarkupParserTextFieldCallback :: C_MarkupParserTextFieldCallback -> IO (FunPtr C_MarkupParserTextFieldCallback)
- noMarkupParserTextFieldCallback :: Maybe MarkupParserTextFieldCallback
- noMarkupParserTextFieldCallback_WithClosures :: Maybe MarkupParserTextFieldCallback_WithClosures
- type C_MemVTableCallocFieldCallback = Word64 -> Word64 -> IO (Ptr ())
- type MemVTableCallocFieldCallback = Word64 -> Word64 -> IO (Ptr ())
- dynamic_MemVTableCallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableCallocFieldCallback -> Word64 -> Word64 -> m (Ptr ())
- genClosure_MemVTableCallocFieldCallback :: MonadIO m => MemVTableCallocFieldCallback -> m (GClosure C_MemVTableCallocFieldCallback)
- mk_MemVTableCallocFieldCallback :: C_MemVTableCallocFieldCallback -> IO (FunPtr C_MemVTableCallocFieldCallback)
- noMemVTableCallocFieldCallback :: Maybe MemVTableCallocFieldCallback
- wrap_MemVTableCallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableCallocFieldCallback)) -> MemVTableCallocFieldCallback -> C_MemVTableCallocFieldCallback
- type C_MemVTableFreeFieldCallback = Ptr () -> IO ()
- type MemVTableFreeFieldCallback = Ptr () -> IO ()
- dynamic_MemVTableFreeFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableFreeFieldCallback -> Ptr () -> m ()
- genClosure_MemVTableFreeFieldCallback :: MonadIO m => MemVTableFreeFieldCallback -> m (GClosure C_MemVTableFreeFieldCallback)
- mk_MemVTableFreeFieldCallback :: C_MemVTableFreeFieldCallback -> IO (FunPtr C_MemVTableFreeFieldCallback)
- noMemVTableFreeFieldCallback :: Maybe MemVTableFreeFieldCallback
- wrap_MemVTableFreeFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableFreeFieldCallback)) -> MemVTableFreeFieldCallback -> C_MemVTableFreeFieldCallback
- type C_MemVTableMallocFieldCallback = Word64 -> IO (Ptr ())
- type MemVTableMallocFieldCallback = Word64 -> IO (Ptr ())
- dynamic_MemVTableMallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableMallocFieldCallback -> Word64 -> m (Ptr ())
- genClosure_MemVTableMallocFieldCallback :: MonadIO m => MemVTableMallocFieldCallback -> m (GClosure C_MemVTableMallocFieldCallback)
- mk_MemVTableMallocFieldCallback :: C_MemVTableMallocFieldCallback -> IO (FunPtr C_MemVTableMallocFieldCallback)
- noMemVTableMallocFieldCallback :: Maybe MemVTableMallocFieldCallback
- wrap_MemVTableMallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableMallocFieldCallback)) -> MemVTableMallocFieldCallback -> C_MemVTableMallocFieldCallback
- type C_MemVTableReallocFieldCallback = Ptr () -> Word64 -> IO (Ptr ())
- type MemVTableReallocFieldCallback = Ptr () -> Word64 -> IO (Ptr ())
- dynamic_MemVTableReallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableReallocFieldCallback -> Ptr () -> Word64 -> m (Ptr ())
- genClosure_MemVTableReallocFieldCallback :: MonadIO m => MemVTableReallocFieldCallback -> m (GClosure C_MemVTableReallocFieldCallback)
- mk_MemVTableReallocFieldCallback :: C_MemVTableReallocFieldCallback -> IO (FunPtr C_MemVTableReallocFieldCallback)
- noMemVTableReallocFieldCallback :: Maybe MemVTableReallocFieldCallback
- wrap_MemVTableReallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableReallocFieldCallback)) -> MemVTableReallocFieldCallback -> C_MemVTableReallocFieldCallback
- type C_MemVTableTryMallocFieldCallback = Word64 -> IO (Ptr ())
- type MemVTableTryMallocFieldCallback = Word64 -> IO (Ptr ())
- dynamic_MemVTableTryMallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableTryMallocFieldCallback -> Word64 -> m (Ptr ())
- genClosure_MemVTableTryMallocFieldCallback :: MonadIO m => MemVTableTryMallocFieldCallback -> m (GClosure C_MemVTableTryMallocFieldCallback)
- mk_MemVTableTryMallocFieldCallback :: C_MemVTableTryMallocFieldCallback -> IO (FunPtr C_MemVTableTryMallocFieldCallback)
- noMemVTableTryMallocFieldCallback :: Maybe MemVTableTryMallocFieldCallback
- wrap_MemVTableTryMallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableTryMallocFieldCallback)) -> MemVTableTryMallocFieldCallback -> C_MemVTableTryMallocFieldCallback
- type C_MemVTableTryReallocFieldCallback = Ptr () -> Word64 -> IO (Ptr ())
- type MemVTableTryReallocFieldCallback = Ptr () -> Word64 -> IO (Ptr ())
- dynamic_MemVTableTryReallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableTryReallocFieldCallback -> Ptr () -> Word64 -> m (Ptr ())
- genClosure_MemVTableTryReallocFieldCallback :: MonadIO m => MemVTableTryReallocFieldCallback -> m (GClosure C_MemVTableTryReallocFieldCallback)
- mk_MemVTableTryReallocFieldCallback :: C_MemVTableTryReallocFieldCallback -> IO (FunPtr C_MemVTableTryReallocFieldCallback)
- noMemVTableTryReallocFieldCallback :: Maybe MemVTableTryReallocFieldCallback
- wrap_MemVTableTryReallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableTryReallocFieldCallback)) -> MemVTableTryReallocFieldCallback -> C_MemVTableTryReallocFieldCallback
- type C_NodeForeachFunc = Ptr Node -> Ptr () -> IO ()
- type NodeForeachFunc = Node -> Ptr () -> IO ()
- dynamic_NodeForeachFunc :: (HasCallStack, MonadIO m) => FunPtr C_NodeForeachFunc -> Node -> Ptr () -> m ()
- genClosure_NodeForeachFunc :: MonadIO m => NodeForeachFunc -> m (GClosure C_NodeForeachFunc)
- mk_NodeForeachFunc :: C_NodeForeachFunc -> IO (FunPtr C_NodeForeachFunc)
- noNodeForeachFunc :: Maybe NodeForeachFunc
- wrap_NodeForeachFunc :: Maybe (Ptr (FunPtr C_NodeForeachFunc)) -> NodeForeachFunc -> C_NodeForeachFunc
- type C_NodeTraverseFunc = Ptr Node -> Ptr () -> IO CInt
- type NodeTraverseFunc = Node -> Ptr () -> IO Bool
- dynamic_NodeTraverseFunc :: (HasCallStack, MonadIO m) => FunPtr C_NodeTraverseFunc -> Node -> Ptr () -> m Bool
- genClosure_NodeTraverseFunc :: MonadIO m => NodeTraverseFunc -> m (GClosure C_NodeTraverseFunc)
- mk_NodeTraverseFunc :: C_NodeTraverseFunc -> IO (FunPtr C_NodeTraverseFunc)
- noNodeTraverseFunc :: Maybe NodeTraverseFunc
- wrap_NodeTraverseFunc :: Maybe (Ptr (FunPtr C_NodeTraverseFunc)) -> NodeTraverseFunc -> C_NodeTraverseFunc
- type C_OptionArgFunc = CString -> CString -> Ptr () -> Ptr (Ptr GError) -> IO CInt
- type OptionArgFunc = Text -> Text -> Ptr () -> IO ()
- dynamic_OptionArgFunc :: (HasCallStack, MonadIO m) => FunPtr C_OptionArgFunc -> Text -> Text -> Ptr () -> m ()
- mk_OptionArgFunc :: C_OptionArgFunc -> IO (FunPtr C_OptionArgFunc)
- noOptionArgFunc :: Maybe OptionArgFunc
- type C_OptionErrorFunc = Ptr OptionContext -> Ptr OptionGroup -> Ptr () -> Ptr (Ptr GError) -> IO ()
- type OptionErrorFunc = OptionContext -> OptionGroup -> Ptr () -> IO ()
- dynamic_OptionErrorFunc :: (HasCallStack, MonadIO m) => FunPtr C_OptionErrorFunc -> OptionContext -> OptionGroup -> Ptr () -> m ()
- mk_OptionErrorFunc :: C_OptionErrorFunc -> IO (FunPtr C_OptionErrorFunc)
- noOptionErrorFunc :: Maybe OptionErrorFunc
- type C_OptionParseFunc = Ptr OptionContext -> Ptr OptionGroup -> Ptr () -> Ptr (Ptr GError) -> IO CInt
- type OptionParseFunc = OptionContext -> OptionGroup -> Ptr () -> IO ()
- dynamic_OptionParseFunc :: (HasCallStack, MonadIO m) => FunPtr C_OptionParseFunc -> OptionContext -> OptionGroup -> Ptr () -> m ()
- mk_OptionParseFunc :: C_OptionParseFunc -> IO (FunPtr C_OptionParseFunc)
- noOptionParseFunc :: Maybe OptionParseFunc
- type C_PollFunc = Ptr PollFD -> Word32 -> Int32 -> IO Int32
- type PollFunc = PollFD -> Word32 -> Int32 -> IO Int32
- dynamic_PollFunc :: (HasCallStack, MonadIO m) => FunPtr C_PollFunc -> PollFD -> Word32 -> Int32 -> m Int32
- genClosure_PollFunc :: MonadIO m => PollFunc -> m (GClosure C_PollFunc)
- mk_PollFunc :: C_PollFunc -> IO (FunPtr C_PollFunc)
- noPollFunc :: Maybe PollFunc
- wrap_PollFunc :: Maybe (Ptr (FunPtr C_PollFunc)) -> PollFunc -> C_PollFunc
- type C_PrintFunc = CString -> IO ()
- type PrintFunc = Text -> IO ()
- dynamic_PrintFunc :: (HasCallStack, MonadIO m) => FunPtr C_PrintFunc -> Text -> m ()
- genClosure_PrintFunc :: MonadIO m => PrintFunc -> m (GClosure C_PrintFunc)
- mk_PrintFunc :: C_PrintFunc -> IO (FunPtr C_PrintFunc)
- noPrintFunc :: Maybe PrintFunc
- wrap_PrintFunc :: Maybe (Ptr (FunPtr C_PrintFunc)) -> PrintFunc -> C_PrintFunc
- type C_RegexEvalCallback = Ptr MatchInfo -> Ptr String -> Ptr () -> IO CInt
- type RegexEvalCallback = MatchInfo -> String -> IO Bool
- type RegexEvalCallback_WithClosures = MatchInfo -> String -> Ptr () -> IO Bool
- drop_closures_RegexEvalCallback :: RegexEvalCallback -> RegexEvalCallback_WithClosures
- dynamic_RegexEvalCallback :: (HasCallStack, MonadIO m) => FunPtr C_RegexEvalCallback -> MatchInfo -> String -> Ptr () -> m Bool
- genClosure_RegexEvalCallback :: MonadIO m => RegexEvalCallback -> m (GClosure C_RegexEvalCallback)
- mk_RegexEvalCallback :: C_RegexEvalCallback -> IO (FunPtr C_RegexEvalCallback)
- noRegexEvalCallback :: Maybe RegexEvalCallback
- noRegexEvalCallback_WithClosures :: Maybe RegexEvalCallback_WithClosures
- wrap_RegexEvalCallback :: Maybe (Ptr (FunPtr C_RegexEvalCallback)) -> RegexEvalCallback_WithClosures -> C_RegexEvalCallback
- type C_ScannerMsgFunc = Ptr Scanner -> CString -> CInt -> IO ()
- type ScannerMsgFunc = Scanner -> Text -> Bool -> IO ()
- dynamic_ScannerMsgFunc :: (HasCallStack, MonadIO m) => FunPtr C_ScannerMsgFunc -> Scanner -> Text -> Bool -> m ()
- genClosure_ScannerMsgFunc :: MonadIO m => ScannerMsgFunc -> m (GClosure C_ScannerMsgFunc)
- mk_ScannerMsgFunc :: C_ScannerMsgFunc -> IO (FunPtr C_ScannerMsgFunc)
- noScannerMsgFunc :: Maybe ScannerMsgFunc
- wrap_ScannerMsgFunc :: Maybe (Ptr (FunPtr C_ScannerMsgFunc)) -> ScannerMsgFunc -> C_ScannerMsgFunc
- type C_SequenceIterCompareFunc = Ptr SequenceIter -> Ptr SequenceIter -> Ptr () -> IO Int32
- type SequenceIterCompareFunc = SequenceIter -> SequenceIter -> Ptr () -> IO Int32
- dynamic_SequenceIterCompareFunc :: (HasCallStack, MonadIO m) => FunPtr C_SequenceIterCompareFunc -> SequenceIter -> SequenceIter -> Ptr () -> m Int32
- genClosure_SequenceIterCompareFunc :: MonadIO m => SequenceIterCompareFunc -> m (GClosure C_SequenceIterCompareFunc)
- mk_SequenceIterCompareFunc :: C_SequenceIterCompareFunc -> IO (FunPtr C_SequenceIterCompareFunc)
- noSequenceIterCompareFunc :: Maybe SequenceIterCompareFunc
- wrap_SequenceIterCompareFunc :: Maybe (Ptr (FunPtr C_SequenceIterCompareFunc)) -> SequenceIterCompareFunc -> C_SequenceIterCompareFunc
- type C_SourceCallbackFuncsRefFieldCallback = Ptr () -> IO ()
- type SourceCallbackFuncsRefFieldCallback = Ptr () -> IO ()
- dynamic_SourceCallbackFuncsRefFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceCallbackFuncsRefFieldCallback -> Ptr () -> m ()
- genClosure_SourceCallbackFuncsRefFieldCallback :: MonadIO m => SourceCallbackFuncsRefFieldCallback -> m (GClosure C_SourceCallbackFuncsRefFieldCallback)
- mk_SourceCallbackFuncsRefFieldCallback :: C_SourceCallbackFuncsRefFieldCallback -> IO (FunPtr C_SourceCallbackFuncsRefFieldCallback)
- noSourceCallbackFuncsRefFieldCallback :: Maybe SourceCallbackFuncsRefFieldCallback
- wrap_SourceCallbackFuncsRefFieldCallback :: Maybe (Ptr (FunPtr C_SourceCallbackFuncsRefFieldCallback)) -> SourceCallbackFuncsRefFieldCallback -> C_SourceCallbackFuncsRefFieldCallback
- type C_SourceCallbackFuncsUnrefFieldCallback = Ptr () -> IO ()
- type SourceCallbackFuncsUnrefFieldCallback = Ptr () -> IO ()
- dynamic_SourceCallbackFuncsUnrefFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceCallbackFuncsUnrefFieldCallback -> Ptr () -> m ()
- genClosure_SourceCallbackFuncsUnrefFieldCallback :: MonadIO m => SourceCallbackFuncsUnrefFieldCallback -> m (GClosure C_SourceCallbackFuncsUnrefFieldCallback)
- mk_SourceCallbackFuncsUnrefFieldCallback :: C_SourceCallbackFuncsUnrefFieldCallback -> IO (FunPtr C_SourceCallbackFuncsUnrefFieldCallback)
- noSourceCallbackFuncsUnrefFieldCallback :: Maybe SourceCallbackFuncsUnrefFieldCallback
- wrap_SourceCallbackFuncsUnrefFieldCallback :: Maybe (Ptr (FunPtr C_SourceCallbackFuncsUnrefFieldCallback)) -> SourceCallbackFuncsUnrefFieldCallback -> C_SourceCallbackFuncsUnrefFieldCallback
- type C_SourceDummyMarshal = IO ()
- type SourceDummyMarshal = IO ()
- dynamic_SourceDummyMarshal :: (HasCallStack, MonadIO m) => FunPtr C_SourceDummyMarshal -> m ()
- genClosure_SourceDummyMarshal :: MonadIO m => SourceDummyMarshal -> m (GClosure C_SourceDummyMarshal)
- mk_SourceDummyMarshal :: C_SourceDummyMarshal -> IO (FunPtr C_SourceDummyMarshal)
- noSourceDummyMarshal :: Maybe SourceDummyMarshal
- wrap_SourceDummyMarshal :: Maybe (Ptr (FunPtr C_SourceDummyMarshal)) -> SourceDummyMarshal -> C_SourceDummyMarshal
- type C_SourceFunc = Ptr () -> IO CInt
- type SourceFunc = IO Bool
- type SourceFunc_WithClosures = Ptr () -> IO Bool
- drop_closures_SourceFunc :: SourceFunc -> SourceFunc_WithClosures
- dynamic_SourceFunc :: (HasCallStack, MonadIO m) => FunPtr C_SourceFunc -> Ptr () -> m Bool
- genClosure_SourceFunc :: MonadIO m => SourceFunc -> m (GClosure C_SourceFunc)
- mk_SourceFunc :: C_SourceFunc -> IO (FunPtr C_SourceFunc)
- noSourceFunc :: Maybe SourceFunc
- noSourceFunc_WithClosures :: Maybe SourceFunc_WithClosures
- wrap_SourceFunc :: Maybe (Ptr (FunPtr C_SourceFunc)) -> SourceFunc_WithClosures -> C_SourceFunc
- type C_SourceFuncsCheckFieldCallback = Ptr Source -> IO CInt
- type SourceFuncsCheckFieldCallback = Source -> IO Bool
- dynamic_SourceFuncsCheckFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceFuncsCheckFieldCallback -> Source -> m Bool
- genClosure_SourceFuncsCheckFieldCallback :: MonadIO m => SourceFuncsCheckFieldCallback -> m (GClosure C_SourceFuncsCheckFieldCallback)
- mk_SourceFuncsCheckFieldCallback :: C_SourceFuncsCheckFieldCallback -> IO (FunPtr C_SourceFuncsCheckFieldCallback)
- noSourceFuncsCheckFieldCallback :: Maybe SourceFuncsCheckFieldCallback
- wrap_SourceFuncsCheckFieldCallback :: Maybe (Ptr (FunPtr C_SourceFuncsCheckFieldCallback)) -> SourceFuncsCheckFieldCallback -> C_SourceFuncsCheckFieldCallback
- type C_SourceFuncsFinalizeFieldCallback = Ptr Source -> IO ()
- type SourceFuncsFinalizeFieldCallback = Source -> IO ()
- dynamic_SourceFuncsFinalizeFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceFuncsFinalizeFieldCallback -> Source -> m ()
- genClosure_SourceFuncsFinalizeFieldCallback :: MonadIO m => SourceFuncsFinalizeFieldCallback -> m (GClosure C_SourceFuncsFinalizeFieldCallback)
- mk_SourceFuncsFinalizeFieldCallback :: C_SourceFuncsFinalizeFieldCallback -> IO (FunPtr C_SourceFuncsFinalizeFieldCallback)
- noSourceFuncsFinalizeFieldCallback :: Maybe SourceFuncsFinalizeFieldCallback
- wrap_SourceFuncsFinalizeFieldCallback :: Maybe (Ptr (FunPtr C_SourceFuncsFinalizeFieldCallback)) -> SourceFuncsFinalizeFieldCallback -> C_SourceFuncsFinalizeFieldCallback
- type C_SourceFuncsPrepareFieldCallback = Ptr Source -> Int32 -> IO CInt
- type SourceFuncsPrepareFieldCallback = Source -> Int32 -> IO Bool
- dynamic_SourceFuncsPrepareFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceFuncsPrepareFieldCallback -> Source -> Int32 -> m Bool
- genClosure_SourceFuncsPrepareFieldCallback :: MonadIO m => SourceFuncsPrepareFieldCallback -> m (GClosure C_SourceFuncsPrepareFieldCallback)
- mk_SourceFuncsPrepareFieldCallback :: C_SourceFuncsPrepareFieldCallback -> IO (FunPtr C_SourceFuncsPrepareFieldCallback)
- noSourceFuncsPrepareFieldCallback :: Maybe SourceFuncsPrepareFieldCallback
- wrap_SourceFuncsPrepareFieldCallback :: Maybe (Ptr (FunPtr C_SourceFuncsPrepareFieldCallback)) -> SourceFuncsPrepareFieldCallback -> C_SourceFuncsPrepareFieldCallback
- type C_SpawnChildSetupFunc = Ptr () -> IO ()
- type SpawnChildSetupFunc = IO ()
- type SpawnChildSetupFunc_WithClosures = Ptr () -> IO ()
- drop_closures_SpawnChildSetupFunc :: SpawnChildSetupFunc -> SpawnChildSetupFunc_WithClosures
- dynamic_SpawnChildSetupFunc :: (HasCallStack, MonadIO m) => FunPtr C_SpawnChildSetupFunc -> Ptr () -> m ()
- genClosure_SpawnChildSetupFunc :: MonadIO m => SpawnChildSetupFunc -> m (GClosure C_SpawnChildSetupFunc)
- mk_SpawnChildSetupFunc :: C_SpawnChildSetupFunc -> IO (FunPtr C_SpawnChildSetupFunc)
- noSpawnChildSetupFunc :: Maybe SpawnChildSetupFunc
- noSpawnChildSetupFunc_WithClosures :: Maybe SpawnChildSetupFunc_WithClosures
- wrap_SpawnChildSetupFunc :: Maybe (Ptr (FunPtr C_SpawnChildSetupFunc)) -> SpawnChildSetupFunc_WithClosures -> C_SpawnChildSetupFunc
- type C_TestDataFunc = Ptr () -> IO ()
- type TestDataFunc = IO ()
- type TestDataFunc_WithClosures = Ptr () -> IO ()
- drop_closures_TestDataFunc :: TestDataFunc -> TestDataFunc_WithClosures
- dynamic_TestDataFunc :: (HasCallStack, MonadIO m) => FunPtr C_TestDataFunc -> Ptr () -> m ()
- genClosure_TestDataFunc :: MonadIO m => TestDataFunc -> m (GClosure C_TestDataFunc)
- mk_TestDataFunc :: C_TestDataFunc -> IO (FunPtr C_TestDataFunc)
- noTestDataFunc :: Maybe TestDataFunc
- noTestDataFunc_WithClosures :: Maybe TestDataFunc_WithClosures
- wrap_TestDataFunc :: Maybe (Ptr (FunPtr C_TestDataFunc)) -> TestDataFunc_WithClosures -> C_TestDataFunc
- type C_TestFixtureFunc = Ptr () -> Ptr () -> IO ()
- type TestFixtureFunc = Ptr () -> IO ()
- type TestFixtureFunc_WithClosures = Ptr () -> Ptr () -> IO ()
- drop_closures_TestFixtureFunc :: TestFixtureFunc -> TestFixtureFunc_WithClosures
- dynamic_TestFixtureFunc :: (HasCallStack, MonadIO m) => FunPtr C_TestFixtureFunc -> Ptr () -> Ptr () -> m ()
- genClosure_TestFixtureFunc :: MonadIO m => TestFixtureFunc -> m (GClosure C_TestFixtureFunc)
- mk_TestFixtureFunc :: C_TestFixtureFunc -> IO (FunPtr C_TestFixtureFunc)
- noTestFixtureFunc :: Maybe TestFixtureFunc
- noTestFixtureFunc_WithClosures :: Maybe TestFixtureFunc_WithClosures
- wrap_TestFixtureFunc :: Maybe (Ptr (FunPtr C_TestFixtureFunc)) -> TestFixtureFunc_WithClosures -> C_TestFixtureFunc
- type C_TestFunc = IO ()
- type TestFunc = IO ()
- dynamic_TestFunc :: (HasCallStack, MonadIO m) => FunPtr C_TestFunc -> m ()
- genClosure_TestFunc :: MonadIO m => TestFunc -> m (GClosure C_TestFunc)
- mk_TestFunc :: C_TestFunc -> IO (FunPtr C_TestFunc)
- noTestFunc :: Maybe TestFunc
- wrap_TestFunc :: Maybe (Ptr (FunPtr C_TestFunc)) -> TestFunc -> C_TestFunc
- type C_TestLogFatalFunc = CString -> CInt -> CString -> Ptr () -> IO CInt
- type TestLogFatalFunc = Text -> [LogLevelFlags] -> Text -> IO Bool
- type TestLogFatalFunc_WithClosures = Text -> [LogLevelFlags] -> Text -> Ptr () -> IO Bool
- drop_closures_TestLogFatalFunc :: TestLogFatalFunc -> TestLogFatalFunc_WithClosures
- dynamic_TestLogFatalFunc :: (HasCallStack, MonadIO m) => FunPtr C_TestLogFatalFunc -> Text -> [LogLevelFlags] -> Text -> Ptr () -> m Bool
- genClosure_TestLogFatalFunc :: MonadIO m => TestLogFatalFunc -> m (GClosure C_TestLogFatalFunc)
- mk_TestLogFatalFunc :: C_TestLogFatalFunc -> IO (FunPtr C_TestLogFatalFunc)
- noTestLogFatalFunc :: Maybe TestLogFatalFunc
- noTestLogFatalFunc_WithClosures :: Maybe TestLogFatalFunc_WithClosures
- wrap_TestLogFatalFunc :: Maybe (Ptr (FunPtr C_TestLogFatalFunc)) -> TestLogFatalFunc_WithClosures -> C_TestLogFatalFunc
- type C_ThreadFunc = Ptr () -> IO (Ptr ())
- type ThreadFunc = Ptr () -> IO (Ptr ())
- dynamic_ThreadFunc :: (HasCallStack, MonadIO m) => FunPtr C_ThreadFunc -> Ptr () -> m (Ptr ())
- genClosure_ThreadFunc :: MonadIO m => ThreadFunc -> m (GClosure C_ThreadFunc)
- mk_ThreadFunc :: C_ThreadFunc -> IO (FunPtr C_ThreadFunc)
- noThreadFunc :: Maybe ThreadFunc
- wrap_ThreadFunc :: Maybe (Ptr (FunPtr C_ThreadFunc)) -> ThreadFunc -> C_ThreadFunc
- type C_TranslateFunc = CString -> Ptr () -> IO CString
- type TranslateFunc = Text -> Ptr () -> IO Text
- dynamic_TranslateFunc :: (HasCallStack, MonadIO m) => FunPtr C_TranslateFunc -> Text -> Ptr () -> m Text
- genClosure_TranslateFunc :: MonadIO m => TranslateFunc -> m (GClosure C_TranslateFunc)
- mk_TranslateFunc :: C_TranslateFunc -> IO (FunPtr C_TranslateFunc)
- noTranslateFunc :: Maybe TranslateFunc
- wrap_TranslateFunc :: Maybe (Ptr (FunPtr C_TranslateFunc)) -> TranslateFunc -> C_TranslateFunc
- type C_TraverseFunc = Ptr () -> Ptr () -> Ptr () -> IO CInt
- type TraverseFunc = Ptr () -> Ptr () -> Ptr () -> IO Bool
- dynamic_TraverseFunc :: (HasCallStack, MonadIO m) => FunPtr C_TraverseFunc -> Ptr () -> Ptr () -> Ptr () -> m Bool
- genClosure_TraverseFunc :: MonadIO m => TraverseFunc -> m (GClosure C_TraverseFunc)
- mk_TraverseFunc :: C_TraverseFunc -> IO (FunPtr C_TraverseFunc)
- noTraverseFunc :: Maybe TraverseFunc
- wrap_TraverseFunc :: Maybe (Ptr (FunPtr C_TraverseFunc)) -> TraverseFunc -> C_TraverseFunc
- type C_UnixFDSourceFunc = Int32 -> CUInt -> Ptr () -> IO CInt
- type UnixFDSourceFunc = Int32 -> [IOCondition] -> IO Bool
- type UnixFDSourceFunc_WithClosures = Int32 -> [IOCondition] -> Ptr () -> IO Bool
- drop_closures_UnixFDSourceFunc :: UnixFDSourceFunc -> UnixFDSourceFunc_WithClosures
- dynamic_UnixFDSourceFunc :: (HasCallStack, MonadIO m) => FunPtr C_UnixFDSourceFunc -> Int32 -> [IOCondition] -> Ptr () -> m Bool
- genClosure_UnixFDSourceFunc :: MonadIO m => UnixFDSourceFunc -> m (GClosure C_UnixFDSourceFunc)
- mk_UnixFDSourceFunc :: C_UnixFDSourceFunc -> IO (FunPtr C_UnixFDSourceFunc)
- noUnixFDSourceFunc :: Maybe UnixFDSourceFunc
- noUnixFDSourceFunc_WithClosures :: Maybe UnixFDSourceFunc_WithClosures
- wrap_UnixFDSourceFunc :: Maybe (Ptr (FunPtr C_UnixFDSourceFunc)) -> UnixFDSourceFunc_WithClosures -> C_UnixFDSourceFunc
- type C_VoidFunc = IO ()
- type VoidFunc = IO ()
- dynamic_VoidFunc :: (HasCallStack, MonadIO m) => FunPtr C_VoidFunc -> m ()
- genClosure_VoidFunc :: MonadIO m => VoidFunc -> m (GClosure C_VoidFunc)
- mk_VoidFunc :: C_VoidFunc -> IO (FunPtr C_VoidFunc)
- noVoidFunc :: Maybe VoidFunc
- wrap_VoidFunc :: Maybe (Ptr (FunPtr C_VoidFunc)) -> VoidFunc -> C_VoidFunc
Signals
ChildWatchFunc
type C_ChildWatchFunc = Int32 -> Int32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ChildWatchFunc Source #
Arguments
| = Int32 | 
 | 
| -> Int32 | 
 | 
| -> IO () | 
Prototype of a GChildWatchSource callback, called when a child
process has exited.  To interpret status, see the documentation
for spawnCheckExitStatus.
type ChildWatchFunc_WithClosures Source #
Arguments
| = Int32 | 
 | 
| -> Int32 | 
 | 
| -> Ptr () | 
 | 
| -> IO () | 
Prototype of a GChildWatchSource callback, called when a child
process has exited.  To interpret status, see the documentation
for spawnCheckExitStatus.
drop_closures_ChildWatchFunc :: ChildWatchFunc -> ChildWatchFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ChildWatchFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_ChildWatchFunc | |
| -> Int32 | 
 | 
| -> Int32 | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ChildWatchFunc :: MonadIO m => ChildWatchFunc -> m (GClosure C_ChildWatchFunc) Source #
Wrap the callback into a GClosure.
mk_ChildWatchFunc :: C_ChildWatchFunc -> IO (FunPtr C_ChildWatchFunc) Source #
Generate a function pointer callable from C code, from a C_ChildWatchFunc.
noChildWatchFunc :: Maybe ChildWatchFunc Source #
A convenience synonym for Nothing :: Maybe ChildWatchFunc
noChildWatchFunc_WithClosures :: Maybe ChildWatchFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe ChildWatchFunc_WithClosures
wrap_ChildWatchFunc :: Maybe (Ptr (FunPtr C_ChildWatchFunc)) -> ChildWatchFunc_WithClosures -> C_ChildWatchFunc Source #
Wrap a ChildWatchFunc into a C_ChildWatchFunc.
ClearHandleFunc
type C_ClearHandleFunc = Word32 -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ClearHandleFunc Source #
Specifies the type of function passed to g_clear_handle_id().
The implementation is expected to free the resource identified
by handleId; for instance, if handleId is a Source ID,
sourceRemove can be used.
Since: 2.56
dynamic_ClearHandleFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_ClearHandleFunc | |
| -> Word32 | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ClearHandleFunc :: MonadIO m => ClearHandleFunc -> m (GClosure C_ClearHandleFunc) Source #
Wrap the callback into a GClosure.
mk_ClearHandleFunc :: C_ClearHandleFunc -> IO (FunPtr C_ClearHandleFunc) Source #
Generate a function pointer callable from C code, from a C_ClearHandleFunc.
noClearHandleFunc :: Maybe ClearHandleFunc Source #
A convenience synonym for Nothing :: Maybe ClearHandleFunc
wrap_ClearHandleFunc :: Maybe (Ptr (FunPtr C_ClearHandleFunc)) -> ClearHandleFunc -> C_ClearHandleFunc Source #
Wrap a ClearHandleFunc into a C_ClearHandleFunc.
CompareDataFunc
type C_CompareDataFunc = Ptr () -> Ptr () -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type CompareDataFunc Source #
Arguments
| = Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO Int32 | Returns: negative value if  | 
Specifies the type of a comparison function used to compare two values. The function should return a negative integer if the first value comes before the second, 0 if they are equal, or a positive integer if the first value comes after the second.
type CompareDataFunc_WithClosures Source #
Arguments
| = Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO Int32 | Returns: negative value if  | 
Specifies the type of a comparison function used to compare two values. The function should return a negative integer if the first value comes before the second, 0 if they are equal, or a positive integer if the first value comes after the second.
drop_closures_CompareDataFunc :: CompareDataFunc -> CompareDataFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_CompareDataFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_CompareDataFunc | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m Int32 | Returns: negative value if  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CompareDataFunc :: MonadIO m => CompareDataFunc -> m (GClosure C_CompareDataFunc) Source #
Wrap the callback into a GClosure.
mk_CompareDataFunc :: C_CompareDataFunc -> IO (FunPtr C_CompareDataFunc) Source #
Generate a function pointer callable from C code, from a C_CompareDataFunc.
noCompareDataFunc :: Maybe CompareDataFunc Source #
A convenience synonym for Nothing :: Maybe CompareDataFunc
noCompareDataFunc_WithClosures :: Maybe CompareDataFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe CompareDataFunc_WithClosures
wrap_CompareDataFunc :: Maybe (Ptr (FunPtr C_CompareDataFunc)) -> CompareDataFunc_WithClosures -> C_CompareDataFunc Source #
Wrap a CompareDataFunc into a C_CompareDataFunc.
CompareFunc
type C_CompareFunc = Ptr () -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type CompareFunc Source #
Arguments
| = Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO Int32 | Returns: negative value if  | 
Specifies the type of a comparison function used to compare two values. The function should return a negative integer if the first value comes before the second, 0 if they are equal, or a positive integer if the first value comes after the second.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_CompareFunc | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m Int32 | Returns: negative value if  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CompareFunc :: MonadIO m => CompareFunc -> m (GClosure C_CompareFunc) Source #
Wrap the callback into a GClosure.
mk_CompareFunc :: C_CompareFunc -> IO (FunPtr C_CompareFunc) Source #
Generate a function pointer callable from C code, from a C_CompareFunc.
noCompareFunc :: Maybe CompareFunc Source #
A convenience synonym for Nothing :: Maybe CompareFunc
wrap_CompareFunc :: Maybe (Ptr (FunPtr C_CompareFunc)) -> CompareFunc -> C_CompareFunc Source #
Wrap a CompareFunc into a C_CompareFunc.
CopyFunc
type C_CopyFunc = Ptr () -> Ptr () -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
Arguments
| = Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO (Ptr ()) | Returns: A pointer to the copy | 
A function of this signature is used to copy the node data when doing a deep-copy of a tree.
Since: 2.4
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_CopyFunc | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m (Ptr ()) | Returns: A pointer to the copy | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CopyFunc :: MonadIO m => CopyFunc -> m (GClosure C_CopyFunc) Source #
Wrap the callback into a GClosure.
mk_CopyFunc :: C_CopyFunc -> IO (FunPtr C_CopyFunc) Source #
Generate a function pointer callable from C code, from a C_CopyFunc.
wrap_CopyFunc :: Maybe (Ptr (FunPtr C_CopyFunc)) -> CopyFunc -> C_CopyFunc Source #
Wrap a CopyFunc into a C_CopyFunc.
DataForeachFunc
type C_DataForeachFunc = Word32 -> Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type DataForeachFunc Source #
Arguments
| = Word32 | 
 | 
| -> Ptr () | 
 | 
| -> IO () | 
Specifies the type of function passed to datasetForeach. It is
called with each GQuark id and associated data element, together
with the userData parameter supplied to datasetForeach.
type DataForeachFunc_WithClosures Source #
Arguments
| = Word32 | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO () | 
Specifies the type of function passed to datasetForeach. It is
called with each GQuark id and associated data element, together
with the userData parameter supplied to datasetForeach.
drop_closures_DataForeachFunc :: DataForeachFunc -> DataForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DataForeachFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_DataForeachFunc | |
| -> Word32 | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DataForeachFunc :: MonadIO m => DataForeachFunc -> m (GClosure C_DataForeachFunc) Source #
Wrap the callback into a GClosure.
mk_DataForeachFunc :: C_DataForeachFunc -> IO (FunPtr C_DataForeachFunc) Source #
Generate a function pointer callable from C code, from a C_DataForeachFunc.
noDataForeachFunc :: Maybe DataForeachFunc Source #
A convenience synonym for Nothing :: Maybe DataForeachFunc
noDataForeachFunc_WithClosures :: Maybe DataForeachFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe DataForeachFunc_WithClosures
wrap_DataForeachFunc :: Maybe (Ptr (FunPtr C_DataForeachFunc)) -> DataForeachFunc_WithClosures -> C_DataForeachFunc Source #
Wrap a DataForeachFunc into a C_DataForeachFunc.
DestroyNotify
type C_DestroyNotify = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type DestroyNotify Source #
Specifies the type of function which is called when a data element is destroyed. It is passed the pointer to the data element and should free any memory and resources allocated for it.
dynamic_DestroyNotify Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_DestroyNotify | |
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DestroyNotify :: MonadIO m => DestroyNotify -> m (GClosure C_DestroyNotify) Source #
Wrap the callback into a GClosure.
mk_DestroyNotify :: C_DestroyNotify -> IO (FunPtr C_DestroyNotify) Source #
Generate a function pointer callable from C code, from a C_DestroyNotify.
noDestroyNotify :: Maybe DestroyNotify Source #
A convenience synonym for Nothing :: Maybe DestroyNotify
wrap_DestroyNotify :: Maybe (Ptr (FunPtr C_DestroyNotify)) -> DestroyNotify -> C_DestroyNotify Source #
Wrap a DestroyNotify into a C_DestroyNotify.
DuplicateFunc
type C_DuplicateFunc = Ptr () -> Ptr () -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
type DuplicateFunc Source #
The type of functions that are used to 'duplicate' an object.
What this means depends on the context, it could just be
incrementing the reference count, if data is a ref-counted
object.
type DuplicateFunc_WithClosures Source #
Arguments
| = Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO (Ptr ()) | Returns: a duplicate of data | 
The type of functions that are used to 'duplicate' an object.
What this means depends on the context, it could just be
incrementing the reference count, if data is a ref-counted
object.
drop_closures_DuplicateFunc :: DuplicateFunc -> DuplicateFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DuplicateFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_DuplicateFunc | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m (Ptr ()) | Returns: a duplicate of data | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DuplicateFunc :: MonadIO m => DuplicateFunc -> m (GClosure C_DuplicateFunc) Source #
Wrap the callback into a GClosure.
mk_DuplicateFunc :: C_DuplicateFunc -> IO (FunPtr C_DuplicateFunc) Source #
Generate a function pointer callable from C code, from a C_DuplicateFunc.
noDuplicateFunc :: Maybe DuplicateFunc Source #
A convenience synonym for Nothing :: Maybe DuplicateFunc
noDuplicateFunc_WithClosures :: Maybe DuplicateFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe DuplicateFunc_WithClosures
wrap_DuplicateFunc :: Maybe (Ptr (FunPtr C_DuplicateFunc)) -> DuplicateFunc_WithClosures -> C_DuplicateFunc Source #
Wrap a DuplicateFunc into a C_DuplicateFunc.
EqualFunc
type C_EqualFunc = Ptr () -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_EqualFunc | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_EqualFunc :: MonadIO m => EqualFunc -> m (GClosure C_EqualFunc) Source #
Wrap the callback into a GClosure.
mk_EqualFunc :: C_EqualFunc -> IO (FunPtr C_EqualFunc) Source #
Generate a function pointer callable from C code, from a C_EqualFunc.
wrap_EqualFunc :: Maybe (Ptr (FunPtr C_EqualFunc)) -> EqualFunc -> C_EqualFunc Source #
Wrap a EqualFunc into a C_EqualFunc.
FreeFunc
type C_FreeFunc = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
Declares a type of function which takes an arbitrary data pointer argument and has no return value. It is not currently used in GLib or GTK+.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_FreeFunc | |
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FreeFunc :: MonadIO m => FreeFunc -> m (GClosure C_FreeFunc) Source #
Wrap the callback into a GClosure.
mk_FreeFunc :: C_FreeFunc -> IO (FunPtr C_FreeFunc) Source #
Generate a function pointer callable from C code, from a C_FreeFunc.
wrap_FreeFunc :: Maybe (Ptr (FunPtr C_FreeFunc)) -> FreeFunc -> C_FreeFunc Source #
Wrap a FreeFunc into a C_FreeFunc.
Func
Specifies the type of functions passed to g_list_foreach() and
g_slist_foreach().
type Func_WithClosures Source #
Arguments
| = Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO () | 
Specifies the type of functions passed to g_list_foreach() and
g_slist_foreach().
drop_closures_Func :: Func -> Func_WithClosures Source #
A simple wrapper that ignores the closure arguments.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_Func | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_Func :: MonadIO m => Func -> m (GClosure C_Func) Source #
Wrap the callback into a GClosure.
mk_Func :: C_Func -> IO (FunPtr C_Func) Source #
Generate a function pointer callable from C code, from a C_Func.
noFunc_WithClosures :: Maybe Func_WithClosures Source #
A convenience synonym for Nothing :: Maybe Func_WithClosures
HFunc
type C_HFunc = Ptr () -> Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
Specifies the type of the function passed to g_hash_table_foreach().
It is called with each key/value pair, together with the userData
parameter which is passed to g_hash_table_foreach().
type HFunc_WithClosures Source #
Arguments
| = Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO () | 
Specifies the type of the function passed to g_hash_table_foreach().
It is called with each key/value pair, together with the userData
parameter which is passed to g_hash_table_foreach().
drop_closures_HFunc :: HFunc -> HFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HFunc | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HFunc :: MonadIO m => HFunc -> m (GClosure C_HFunc) Source #
Wrap the callback into a GClosure.
mk_HFunc :: C_HFunc -> IO (FunPtr C_HFunc) Source #
Generate a function pointer callable from C code, from a C_HFunc.
noHFunc_WithClosures :: Maybe HFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe HFunc_WithClosures
wrap_HFunc :: Maybe (Ptr (FunPtr C_HFunc)) -> HFunc_WithClosures -> C_HFunc Source #
HRFunc
type C_HRFunc = Ptr () -> Ptr () -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type HRFunc_WithClosures Source #
drop_closures_HRFunc :: HRFunc -> HRFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HRFunc | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | Returns:  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HRFunc :: MonadIO m => HRFunc -> m (GClosure C_HRFunc) Source #
Wrap the callback into a GClosure.
mk_HRFunc :: C_HRFunc -> IO (FunPtr C_HRFunc) Source #
Generate a function pointer callable from C code, from a C_HRFunc.
noHRFunc_WithClosures :: Maybe HRFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe HRFunc_WithClosures
wrap_HRFunc :: Maybe (Ptr (FunPtr C_HRFunc)) -> HRFunc_WithClosures -> C_HRFunc Source #
HashFunc
Specifies the type of the hash function which is passed to
g_hash_table_new() when a HashTable is created.
The function is passed a key and should return a guint hash value.
The functions directHash, intHash and strHash provide
hash functions which can be used when the key is a gpointer, gint*,
and gchar* respectively.
directHash is also the appropriate hash function for keys
of the form GINT_TO_POINTER (n) (or similar macros).
A good hash functions should produce hash values that are evenly distributed over a fairly large range. The modulus is taken with the hash table size (a prime number) to find the 'bucket' to place each key into. The function should also be very fast, since it is called for each key lookup.
Note that the hash functions provided by GLib have these qualities,
but are not particularly robust against manufactured keys that
cause hash collisions. Therefore, you should consider choosing
a more secure hash function when using a GHashTable with keys
that originate in untrusted data (such as HTTP requests).
Using strHash in that situation might make your application
vulerable to
Algorithmic Complexity Attacks.
The key to choosing a good hash is unpredictability. Even cryptographic hashes are very easy to find collisions for when the remainder is taken modulo a somewhat predictable prime number. There must be an element of randomness that an attacker is unable to guess.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HashFunc | |
| -> Ptr () | 
 | 
| -> m Word32 | Returns: the hash value corresponding to the key | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HashFunc :: MonadIO m => HashFunc -> m (GClosure C_HashFunc) Source #
Wrap the callback into a GClosure.
mk_HashFunc :: C_HashFunc -> IO (FunPtr C_HashFunc) Source #
Generate a function pointer callable from C code, from a C_HashFunc.
wrap_HashFunc :: Maybe (Ptr (FunPtr C_HashFunc)) -> HashFunc -> C_HashFunc Source #
Wrap a HashFunc into a C_HashFunc.
HookCheckFunc
type HookCheckFunc Source #
Defines the type of a hook function that can be invoked
by hookListInvokeCheck.
dynamic_HookCheckFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HookCheckFunc | |
| -> Ptr () | 
 | 
| -> m Bool | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HookCheckFunc :: MonadIO m => HookCheckFunc -> m (GClosure C_HookCheckFunc) Source #
Wrap the callback into a GClosure.
mk_HookCheckFunc :: C_HookCheckFunc -> IO (FunPtr C_HookCheckFunc) Source #
Generate a function pointer callable from C code, from a C_HookCheckFunc.
noHookCheckFunc :: Maybe HookCheckFunc Source #
A convenience synonym for Nothing :: Maybe HookCheckFunc
wrap_HookCheckFunc :: Maybe (Ptr (FunPtr C_HookCheckFunc)) -> HookCheckFunc -> C_HookCheckFunc Source #
Wrap a HookCheckFunc into a C_HookCheckFunc.
HookCheckMarshaller
type C_HookCheckMarshaller = Ptr Hook -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type HookCheckMarshaller Source #
Arguments
| = Hook | 
 | 
| -> Ptr () | 
 | 
| -> IO Bool | Returns:  | 
Defines the type of function used by g_hook_list_marshal_check().
dynamic_HookCheckMarshaller Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HookCheckMarshaller | |
| -> Hook | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | Returns:  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HookCheckMarshaller :: MonadIO m => HookCheckMarshaller -> m (GClosure C_HookCheckMarshaller) Source #
Wrap the callback into a GClosure.
mk_HookCheckMarshaller :: C_HookCheckMarshaller -> IO (FunPtr C_HookCheckMarshaller) Source #
Generate a function pointer callable from C code, from a C_HookCheckMarshaller.
noHookCheckMarshaller :: Maybe HookCheckMarshaller Source #
A convenience synonym for Nothing :: Maybe HookCheckMarshaller
wrap_HookCheckMarshaller :: Maybe (Ptr (FunPtr C_HookCheckMarshaller)) -> HookCheckMarshaller -> C_HookCheckMarshaller Source #
Wrap a HookCheckMarshaller into a C_HookCheckMarshaller.
HookCompareFunc
type C_HookCompareFunc = Ptr Hook -> Ptr Hook -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type HookCompareFunc Source #
Arguments
| = Hook | 
 | 
| -> Hook | 
 | 
| -> IO Int32 | Returns: a value <= 0 if  | 
Defines the type of function used to compare Hook elements in
g_hook_insert_sorted().
dynamic_HookCompareFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HookCompareFunc | |
| -> Hook | 
 | 
| -> Hook | 
 | 
| -> m Int32 | Returns: a value <= 0 if  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HookCompareFunc :: MonadIO m => HookCompareFunc -> m (GClosure C_HookCompareFunc) Source #
Wrap the callback into a GClosure.
mk_HookCompareFunc :: C_HookCompareFunc -> IO (FunPtr C_HookCompareFunc) Source #
Generate a function pointer callable from C code, from a C_HookCompareFunc.
noHookCompareFunc :: Maybe HookCompareFunc Source #
A convenience synonym for Nothing :: Maybe HookCompareFunc
wrap_HookCompareFunc :: Maybe (Ptr (FunPtr C_HookCompareFunc)) -> HookCompareFunc -> C_HookCompareFunc Source #
Wrap a HookCompareFunc into a C_HookCompareFunc.
HookFinalizeFunc
type C_HookFinalizeFunc = Ptr HookList -> Ptr Hook -> IO () Source #
Type for the callback on the (unwrapped) C side.
type HookFinalizeFunc Source #
Arguments
| = HookList | 
 | 
| -> Hook | 
 | 
| -> IO () | 
Defines the type of function to be called when a hook in a list of hooks gets finalized.
dynamic_HookFinalizeFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HookFinalizeFunc | |
| -> HookList | 
 | 
| -> Hook | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HookFinalizeFunc :: MonadIO m => HookFinalizeFunc -> m (GClosure C_HookFinalizeFunc) Source #
Wrap the callback into a GClosure.
mk_HookFinalizeFunc :: C_HookFinalizeFunc -> IO (FunPtr C_HookFinalizeFunc) Source #
Generate a function pointer callable from C code, from a C_HookFinalizeFunc.
noHookFinalizeFunc :: Maybe HookFinalizeFunc Source #
A convenience synonym for Nothing :: Maybe HookFinalizeFunc
wrap_HookFinalizeFunc :: Maybe (Ptr (FunPtr C_HookFinalizeFunc)) -> HookFinalizeFunc -> C_HookFinalizeFunc Source #
Wrap a HookFinalizeFunc into a C_HookFinalizeFunc.
HookFindFunc
type C_HookFindFunc = Ptr Hook -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type HookFindFunc Source #
Defines the type of the function passed to g_hook_find().
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HookFindFunc | |
| -> Hook | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HookFindFunc :: MonadIO m => HookFindFunc -> m (GClosure C_HookFindFunc) Source #
Wrap the callback into a GClosure.
mk_HookFindFunc :: C_HookFindFunc -> IO (FunPtr C_HookFindFunc) Source #
Generate a function pointer callable from C code, from a C_HookFindFunc.
noHookFindFunc :: Maybe HookFindFunc Source #
A convenience synonym for Nothing :: Maybe HookFindFunc
wrap_HookFindFunc :: Maybe (Ptr (FunPtr C_HookFindFunc)) -> HookFindFunc -> C_HookFindFunc Source #
Wrap a HookFindFunc into a C_HookFindFunc.
HookFunc
type C_HookFunc = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
Defines the type of a hook function that can be invoked
by hookListInvoke.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HookFunc | |
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HookFunc :: MonadIO m => HookFunc -> m (GClosure C_HookFunc) Source #
Wrap the callback into a GClosure.
mk_HookFunc :: C_HookFunc -> IO (FunPtr C_HookFunc) Source #
Generate a function pointer callable from C code, from a C_HookFunc.
wrap_HookFunc :: Maybe (Ptr (FunPtr C_HookFunc)) -> HookFunc -> C_HookFunc Source #
Wrap a HookFunc into a C_HookFunc.
HookMarshaller
type C_HookMarshaller = Ptr Hook -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type HookMarshaller Source #
Defines the type of function used by g_hook_list_marshal().
dynamic_HookMarshaller Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_HookMarshaller | |
| -> Hook | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_HookMarshaller :: MonadIO m => HookMarshaller -> m (GClosure C_HookMarshaller) Source #
Wrap the callback into a GClosure.
mk_HookMarshaller :: C_HookMarshaller -> IO (FunPtr C_HookMarshaller) Source #
Generate a function pointer callable from C code, from a C_HookMarshaller.
noHookMarshaller :: Maybe HookMarshaller Source #
A convenience synonym for Nothing :: Maybe HookMarshaller
wrap_HookMarshaller :: Maybe (Ptr (FunPtr C_HookMarshaller)) -> HookMarshaller -> C_HookMarshaller Source #
Wrap a HookMarshaller into a C_HookMarshaller.
IOFunc
type C_IOFunc = Ptr IOChannel -> CUInt -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
Arguments
| = IOChannel | 
 | 
| -> [IOCondition] | 
 | 
| -> Ptr () | 
 | 
| -> IO Bool | Returns: the function should return  | 
Specifies the type of function passed to g_io_add_watch() or
ioAddWatch, which is called when the requested condition
on a IOChannel is satisfied.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_IOFunc | |
| -> IOChannel | 
 | 
| -> [IOCondition] | 
 | 
| -> 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_IOFunc :: MonadIO m => IOFunc -> m (GClosure C_IOFunc) Source #
Wrap the callback into a GClosure.
mk_IOFunc :: C_IOFunc -> IO (FunPtr C_IOFunc) Source #
Generate a function pointer callable from C code, from a C_IOFunc.
IOFuncsIoCloseFieldCallback
type C_IOFuncsIoCloseFieldCallback = Ptr IOChannel -> Ptr (Ptr GError) -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type IOFuncsIoCloseFieldCallback Source #
No description available in the introspection data.
dynamic_IOFuncsIoCloseFieldCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_IOFuncsIoCloseFieldCallback | |
| -> IOChannel | |
| -> m IOStatus | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_IOFuncsIoCloseFieldCallback :: C_IOFuncsIoCloseFieldCallback -> IO (FunPtr C_IOFuncsIoCloseFieldCallback) Source #
Generate a function pointer callable from C code, from a C_IOFuncsIoCloseFieldCallback.
noIOFuncsIoCloseFieldCallback :: Maybe IOFuncsIoCloseFieldCallback Source #
A convenience synonym for Nothing :: Maybe IOFuncsIoCloseFieldCallback
IOFuncsIoCreateWatchFieldCallback
type C_IOFuncsIoCreateWatchFieldCallback = Ptr IOChannel -> CUInt -> IO (Ptr Source) Source #
Type for the callback on the (unwrapped) C side.
type IOFuncsIoCreateWatchFieldCallback = IOChannel -> [IOCondition] -> IO Source Source #
No description available in the introspection data.
dynamic_IOFuncsIoCreateWatchFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoCreateWatchFieldCallback -> IOChannel -> [IOCondition] -> m Source Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IOFuncsIoCreateWatchFieldCallback :: MonadIO m => IOFuncsIoCreateWatchFieldCallback -> m (GClosure C_IOFuncsIoCreateWatchFieldCallback) Source #
Wrap the callback into a GClosure.
mk_IOFuncsIoCreateWatchFieldCallback :: C_IOFuncsIoCreateWatchFieldCallback -> IO (FunPtr C_IOFuncsIoCreateWatchFieldCallback) Source #
Generate a function pointer callable from C code, from a C_IOFuncsIoCreateWatchFieldCallback.
noIOFuncsIoCreateWatchFieldCallback :: Maybe IOFuncsIoCreateWatchFieldCallback Source #
A convenience synonym for Nothing :: Maybe IOFuncsIoCreateWatchFieldCallback
wrap_IOFuncsIoCreateWatchFieldCallback :: Maybe (Ptr (FunPtr C_IOFuncsIoCreateWatchFieldCallback)) -> IOFuncsIoCreateWatchFieldCallback -> C_IOFuncsIoCreateWatchFieldCallback Source #
IOFuncsIoFreeFieldCallback
type C_IOFuncsIoFreeFieldCallback = Ptr IOChannel -> IO () Source #
Type for the callback on the (unwrapped) C side.
type IOFuncsIoFreeFieldCallback = IOChannel -> IO () Source #
No description available in the introspection data.
dynamic_IOFuncsIoFreeFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoFreeFieldCallback -> IOChannel -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IOFuncsIoFreeFieldCallback :: MonadIO m => IOFuncsIoFreeFieldCallback -> m (GClosure C_IOFuncsIoFreeFieldCallback) Source #
Wrap the callback into a GClosure.
mk_IOFuncsIoFreeFieldCallback :: C_IOFuncsIoFreeFieldCallback -> IO (FunPtr C_IOFuncsIoFreeFieldCallback) Source #
Generate a function pointer callable from C code, from a C_IOFuncsIoFreeFieldCallback.
noIOFuncsIoFreeFieldCallback :: Maybe IOFuncsIoFreeFieldCallback Source #
A convenience synonym for Nothing :: Maybe IOFuncsIoFreeFieldCallback
wrap_IOFuncsIoFreeFieldCallback :: Maybe (Ptr (FunPtr C_IOFuncsIoFreeFieldCallback)) -> IOFuncsIoFreeFieldCallback -> C_IOFuncsIoFreeFieldCallback Source #
Wrap a IOFuncsIoFreeFieldCallback into a C_IOFuncsIoFreeFieldCallback.
IOFuncsIoGetFlagsFieldCallback
type C_IOFuncsIoGetFlagsFieldCallback = Ptr IOChannel -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type IOFuncsIoGetFlagsFieldCallback = IOChannel -> IO [IOFlags] Source #
No description available in the introspection data.
dynamic_IOFuncsIoGetFlagsFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_IOFuncsIoGetFlagsFieldCallback -> IOChannel -> m [IOFlags] Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IOFuncsIoGetFlagsFieldCallback :: MonadIO m => IOFuncsIoGetFlagsFieldCallback -> m (GClosure C_IOFuncsIoGetFlagsFieldCallback) Source #
Wrap the callback into a GClosure.
mk_IOFuncsIoGetFlagsFieldCallback :: C_IOFuncsIoGetFlagsFieldCallback -> IO (FunPtr C_IOFuncsIoGetFlagsFieldCallback) Source #
Generate a function pointer callable from C code, from a C_IOFuncsIoGetFlagsFieldCallback.
noIOFuncsIoGetFlagsFieldCallback :: Maybe IOFuncsIoGetFlagsFieldCallback Source #
A convenience synonym for Nothing :: Maybe IOFuncsIoGetFlagsFieldCallback
wrap_IOFuncsIoGetFlagsFieldCallback :: Maybe (Ptr (FunPtr C_IOFuncsIoGetFlagsFieldCallback)) -> IOFuncsIoGetFlagsFieldCallback -> C_IOFuncsIoGetFlagsFieldCallback Source #
Wrap a IOFuncsIoGetFlagsFieldCallback into a C_IOFuncsIoGetFlagsFieldCallback.
IOFuncsIoReadFieldCallback
type C_IOFuncsIoReadFieldCallback = Ptr IOChannel -> CString -> Word64 -> Word64 -> Ptr (Ptr GError) -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type IOFuncsIoReadFieldCallback Source #
No description available in the introspection data.
dynamic_IOFuncsIoReadFieldCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_IOFuncsIoReadFieldCallback | |
| -> IOChannel | |
| -> Text | |
| -> Word64 | |
| -> Word64 | |
| -> m IOStatus | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_IOFuncsIoReadFieldCallback :: C_IOFuncsIoReadFieldCallback -> IO (FunPtr C_IOFuncsIoReadFieldCallback) Source #
Generate a function pointer callable from C code, from a C_IOFuncsIoReadFieldCallback.
noIOFuncsIoReadFieldCallback :: Maybe IOFuncsIoReadFieldCallback Source #
A convenience synonym for Nothing :: Maybe IOFuncsIoReadFieldCallback
IOFuncsIoSeekFieldCallback
type C_IOFuncsIoSeekFieldCallback = Ptr IOChannel -> Int64 -> CUInt -> Ptr (Ptr GError) -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type IOFuncsIoSeekFieldCallback Source #
No description available in the introspection data.
dynamic_IOFuncsIoSeekFieldCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_IOFuncsIoSeekFieldCallback | |
| -> IOChannel | |
| -> Int64 | |
| -> SeekType | |
| -> m IOStatus | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_IOFuncsIoSeekFieldCallback :: C_IOFuncsIoSeekFieldCallback -> IO (FunPtr C_IOFuncsIoSeekFieldCallback) Source #
Generate a function pointer callable from C code, from a C_IOFuncsIoSeekFieldCallback.
noIOFuncsIoSeekFieldCallback :: Maybe IOFuncsIoSeekFieldCallback Source #
A convenience synonym for Nothing :: Maybe IOFuncsIoSeekFieldCallback
IOFuncsIoSetFlagsFieldCallback
type C_IOFuncsIoSetFlagsFieldCallback = Ptr IOChannel -> CUInt -> Ptr (Ptr GError) -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type IOFuncsIoSetFlagsFieldCallback Source #
No description available in the introspection data.
dynamic_IOFuncsIoSetFlagsFieldCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_IOFuncsIoSetFlagsFieldCallback | |
| -> IOChannel | |
| -> [IOFlags] | |
| -> m IOStatus | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_IOFuncsIoSetFlagsFieldCallback :: C_IOFuncsIoSetFlagsFieldCallback -> IO (FunPtr C_IOFuncsIoSetFlagsFieldCallback) Source #
Generate a function pointer callable from C code, from a C_IOFuncsIoSetFlagsFieldCallback.
noIOFuncsIoSetFlagsFieldCallback :: Maybe IOFuncsIoSetFlagsFieldCallback Source #
A convenience synonym for Nothing :: Maybe IOFuncsIoSetFlagsFieldCallback
IOFuncsIoWriteFieldCallback
type C_IOFuncsIoWriteFieldCallback = Ptr IOChannel -> CString -> Word64 -> Word64 -> Ptr (Ptr GError) -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type IOFuncsIoWriteFieldCallback Source #
No description available in the introspection data.
dynamic_IOFuncsIoWriteFieldCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_IOFuncsIoWriteFieldCallback | |
| -> IOChannel | |
| -> Text | |
| -> Word64 | |
| -> Word64 | |
| -> m IOStatus | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_IOFuncsIoWriteFieldCallback :: C_IOFuncsIoWriteFieldCallback -> IO (FunPtr C_IOFuncsIoWriteFieldCallback) Source #
Generate a function pointer callable from C code, from a C_IOFuncsIoWriteFieldCallback.
noIOFuncsIoWriteFieldCallback :: Maybe IOFuncsIoWriteFieldCallback Source #
A convenience synonym for Nothing :: Maybe IOFuncsIoWriteFieldCallback
LogFunc
type C_LogFunc = CString -> CInt -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
Arguments
| = Text | 
 | 
| -> [LogLevelFlags] | 
 | 
| -> Text | 
 | 
| -> IO () | 
Specifies the prototype of log handler functions.
The default log handler, logDefaultHandler, automatically appends a
new-line character to message when printing it. It is advised that any
custom log handler functions behave similarly, so that logging calls in user
code do not need modifying to add a new-line character to the message if the
log handler is changed.
This is not used if structured logging is enabled; see [Using Structured Logging][using-structured-logging].
type LogFunc_WithClosures Source #
Arguments
| = Text | 
 | 
| -> [LogLevelFlags] | 
 | 
| -> Text | 
 | 
| -> Ptr () | 
 | 
| -> IO () | 
Specifies the prototype of log handler functions.
The default log handler, logDefaultHandler, automatically appends a
new-line character to message when printing it. It is advised that any
custom log handler functions behave similarly, so that logging calls in user
code do not need modifying to add a new-line character to the message if the
log handler is changed.
This is not used if structured logging is enabled; see [Using Structured Logging][using-structured-logging].
drop_closures_LogFunc :: LogFunc -> LogFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_LogFunc | |
| -> Text | 
 | 
| -> [LogLevelFlags] | 
 | 
| -> Text | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_LogFunc :: MonadIO m => LogFunc -> m (GClosure C_LogFunc) Source #
Wrap the callback into a GClosure.
mk_LogFunc :: C_LogFunc -> IO (FunPtr C_LogFunc) Source #
Generate a function pointer callable from C code, from a C_LogFunc.
noLogFunc_WithClosures :: Maybe LogFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe LogFunc_WithClosures
wrap_LogFunc :: Maybe (Ptr (FunPtr C_LogFunc)) -> LogFunc_WithClosures -> C_LogFunc Source #
LogWriterFunc
type C_LogWriterFunc = CInt -> Ptr LogField -> Word64 -> Ptr () -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type LogWriterFunc Source #
Arguments
| = [LogLevelFlags] | 
 | 
| -> [LogField] | 
 | 
| -> IO LogWriterOutput | Returns:  | 
Writer function for log entries. A log entry is a collection of one or more
GLogFields, using the standard <https://www.freedesktop.org/software/systemd/man/systemd.journal-fields.html field names from journal
specification>.
See g_log_structured() for more information.
Writer functions must ignore fields which they do not recognise, unless they can write arbitrary binary output, as field values may be arbitrary binary.
logLevel is guaranteed to be included in fields as the PRIORITY field,
but is provided separately for convenience of deciding whether or where to
output the log entry.
Writer functions should return LogWriterOutputHandled if they handled the log
message successfully or if they deliberately ignored it. If there was an
error handling the message (for example, if the writer function is meant to
send messages to a remote logging server and there is a network error), it
should return LogWriterOutputUnhandled. This allows writer functions to be
chained and fall back to simpler handlers in case of failure.
Since: 2.50
type LogWriterFunc_WithClosures Source #
Arguments
| = [LogLevelFlags] | 
 | 
| -> [LogField] | 
 | 
| -> Ptr () | 
 | 
| -> IO LogWriterOutput | Returns:  | 
Writer function for log entries. A log entry is a collection of one or more
GLogFields, using the standard <https://www.freedesktop.org/software/systemd/man/systemd.journal-fields.html field names from journal
specification>.
See g_log_structured() for more information.
Writer functions must ignore fields which they do not recognise, unless they can write arbitrary binary output, as field values may be arbitrary binary.
logLevel is guaranteed to be included in fields as the PRIORITY field,
but is provided separately for convenience of deciding whether or where to
output the log entry.
Writer functions should return LogWriterOutputHandled if they handled the log
message successfully or if they deliberately ignored it. If there was an
error handling the message (for example, if the writer function is meant to
send messages to a remote logging server and there is a network error), it
should return LogWriterOutputUnhandled. This allows writer functions to be
chained and fall back to simpler handlers in case of failure.
Since: 2.50
drop_closures_LogWriterFunc :: LogWriterFunc -> LogWriterFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_LogWriterFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_LogWriterFunc | |
| -> [LogLevelFlags] | 
 | 
| -> [LogField] | 
 | 
| -> Ptr () | 
 | 
| -> m LogWriterOutput | Returns:  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_LogWriterFunc :: MonadIO m => LogWriterFunc -> m (GClosure C_LogWriterFunc) Source #
Wrap the callback into a GClosure.
mk_LogWriterFunc :: C_LogWriterFunc -> IO (FunPtr C_LogWriterFunc) Source #
Generate a function pointer callable from C code, from a C_LogWriterFunc.
noLogWriterFunc :: Maybe LogWriterFunc Source #
A convenience synonym for Nothing :: Maybe LogWriterFunc
noLogWriterFunc_WithClosures :: Maybe LogWriterFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe LogWriterFunc_WithClosures
wrap_LogWriterFunc :: Maybe (Ptr (FunPtr C_LogWriterFunc)) -> LogWriterFunc_WithClosures -> C_LogWriterFunc Source #
Wrap a LogWriterFunc into a C_LogWriterFunc.
MarkupParserEndElementFieldCallback
type C_MarkupParserEndElementFieldCallback = Ptr MarkupParseContext -> CString -> Ptr () -> Ptr (Ptr GError) -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MarkupParserEndElementFieldCallback Source #
Arguments
| = MarkupParseContext | |
| -> Text | |
| -> IO () | (Can throw  | 
No description available in the introspection data.
type MarkupParserEndElementFieldCallback_WithClosures Source #
Arguments
| = MarkupParseContext | |
| -> Text | |
| -> Ptr () | |
| -> IO () | (Can throw  | 
No description available in the introspection data.
drop_closures_MarkupParserEndElementFieldCallback :: MarkupParserEndElementFieldCallback -> MarkupParserEndElementFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_MarkupParserEndElementFieldCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_MarkupParserEndElementFieldCallback | |
| -> MarkupParseContext | |
| -> Text | |
| -> Ptr () | |
| -> m () | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_MarkupParserEndElementFieldCallback :: C_MarkupParserEndElementFieldCallback -> IO (FunPtr C_MarkupParserEndElementFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MarkupParserEndElementFieldCallback.
noMarkupParserEndElementFieldCallback :: Maybe MarkupParserEndElementFieldCallback Source #
A convenience synonym for Nothing :: Maybe MarkupParserEndElementFieldCallback
noMarkupParserEndElementFieldCallback_WithClosures :: Maybe MarkupParserEndElementFieldCallback_WithClosures Source #
A convenience synonym for Nothing :: Maybe MarkupParserEndElementFieldCallback_WithClosures
MarkupParserErrorFieldCallback
type C_MarkupParserErrorFieldCallback = Ptr MarkupParseContext -> Ptr GError -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MarkupParserErrorFieldCallback = MarkupParseContext -> GError -> IO () Source #
No description available in the introspection data.
type MarkupParserErrorFieldCallback_WithClosures = MarkupParseContext -> GError -> Ptr () -> IO () Source #
No description available in the introspection data.
drop_closures_MarkupParserErrorFieldCallback :: MarkupParserErrorFieldCallback -> MarkupParserErrorFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_MarkupParserErrorFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MarkupParserErrorFieldCallback -> MarkupParseContext -> GError -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MarkupParserErrorFieldCallback :: MonadIO m => MarkupParserErrorFieldCallback -> m (GClosure C_MarkupParserErrorFieldCallback) Source #
Wrap the callback into a GClosure.
mk_MarkupParserErrorFieldCallback :: C_MarkupParserErrorFieldCallback -> IO (FunPtr C_MarkupParserErrorFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MarkupParserErrorFieldCallback.
noMarkupParserErrorFieldCallback :: Maybe MarkupParserErrorFieldCallback Source #
A convenience synonym for Nothing :: Maybe MarkupParserErrorFieldCallback
noMarkupParserErrorFieldCallback_WithClosures :: Maybe MarkupParserErrorFieldCallback_WithClosures Source #
A convenience synonym for Nothing :: Maybe MarkupParserErrorFieldCallback_WithClosures
wrap_MarkupParserErrorFieldCallback :: Maybe (Ptr (FunPtr C_MarkupParserErrorFieldCallback)) -> MarkupParserErrorFieldCallback_WithClosures -> C_MarkupParserErrorFieldCallback Source #
Wrap a MarkupParserErrorFieldCallback into a C_MarkupParserErrorFieldCallback.
MarkupParserPassthroughFieldCallback
type C_MarkupParserPassthroughFieldCallback = Ptr MarkupParseContext -> CString -> Word64 -> Ptr () -> Ptr (Ptr GError) -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MarkupParserPassthroughFieldCallback Source #
Arguments
| = MarkupParseContext | |
| -> Text | |
| -> Word64 | |
| -> IO () | (Can throw  | 
No description available in the introspection data.
type MarkupParserPassthroughFieldCallback_WithClosures Source #
No description available in the introspection data.
drop_closures_MarkupParserPassthroughFieldCallback :: MarkupParserPassthroughFieldCallback -> MarkupParserPassthroughFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_MarkupParserPassthroughFieldCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_MarkupParserPassthroughFieldCallback | |
| -> MarkupParseContext | |
| -> Text | |
| -> Word64 | |
| -> Ptr () | |
| -> m () | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_MarkupParserPassthroughFieldCallback :: C_MarkupParserPassthroughFieldCallback -> IO (FunPtr C_MarkupParserPassthroughFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MarkupParserPassthroughFieldCallback.
noMarkupParserPassthroughFieldCallback :: Maybe MarkupParserPassthroughFieldCallback Source #
A convenience synonym for Nothing :: Maybe MarkupParserPassthroughFieldCallback
noMarkupParserPassthroughFieldCallback_WithClosures :: Maybe MarkupParserPassthroughFieldCallback_WithClosures Source #
A convenience synonym for Nothing :: Maybe MarkupParserPassthroughFieldCallback_WithClosures
MarkupParserStartElementFieldCallback
type C_MarkupParserStartElementFieldCallback = Ptr MarkupParseContext -> CString -> CString -> CString -> Ptr () -> Ptr (Ptr GError) -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MarkupParserStartElementFieldCallback Source #
No description available in the introspection data.
type MarkupParserStartElementFieldCallback_WithClosures Source #
No description available in the introspection data.
drop_closures_MarkupParserStartElementFieldCallback :: MarkupParserStartElementFieldCallback -> MarkupParserStartElementFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_MarkupParserStartElementFieldCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_MarkupParserStartElementFieldCallback | |
| -> MarkupParseContext | |
| -> Text | |
| -> Text | |
| -> Text | |
| -> Ptr () | |
| -> m () | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_MarkupParserStartElementFieldCallback :: C_MarkupParserStartElementFieldCallback -> IO (FunPtr C_MarkupParserStartElementFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MarkupParserStartElementFieldCallback.
noMarkupParserStartElementFieldCallback :: Maybe MarkupParserStartElementFieldCallback Source #
A convenience synonym for Nothing :: Maybe MarkupParserStartElementFieldCallback
noMarkupParserStartElementFieldCallback_WithClosures :: Maybe MarkupParserStartElementFieldCallback_WithClosures Source #
A convenience synonym for Nothing :: Maybe MarkupParserStartElementFieldCallback_WithClosures
MarkupParserTextFieldCallback
type C_MarkupParserTextFieldCallback = Ptr MarkupParseContext -> CString -> Word64 -> Ptr () -> Ptr (Ptr GError) -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MarkupParserTextFieldCallback Source #
Arguments
| = MarkupParseContext | |
| -> Text | |
| -> Word64 | |
| -> IO () | (Can throw  | 
No description available in the introspection data.
type MarkupParserTextFieldCallback_WithClosures Source #
No description available in the introspection data.
drop_closures_MarkupParserTextFieldCallback :: MarkupParserTextFieldCallback -> MarkupParserTextFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_MarkupParserTextFieldCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_MarkupParserTextFieldCallback | |
| -> MarkupParseContext | |
| -> Text | |
| -> Word64 | |
| -> Ptr () | |
| -> m () | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_MarkupParserTextFieldCallback :: C_MarkupParserTextFieldCallback -> IO (FunPtr C_MarkupParserTextFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MarkupParserTextFieldCallback.
noMarkupParserTextFieldCallback :: Maybe MarkupParserTextFieldCallback Source #
A convenience synonym for Nothing :: Maybe MarkupParserTextFieldCallback
noMarkupParserTextFieldCallback_WithClosures :: Maybe MarkupParserTextFieldCallback_WithClosures Source #
A convenience synonym for Nothing :: Maybe MarkupParserTextFieldCallback_WithClosures
MemVTableCallocFieldCallback
type C_MemVTableCallocFieldCallback = Word64 -> Word64 -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
type MemVTableCallocFieldCallback = Word64 -> Word64 -> IO (Ptr ()) Source #
No description available in the introspection data.
dynamic_MemVTableCallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableCallocFieldCallback -> Word64 -> Word64 -> m (Ptr ()) Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemVTableCallocFieldCallback :: MonadIO m => MemVTableCallocFieldCallback -> m (GClosure C_MemVTableCallocFieldCallback) Source #
Wrap the callback into a GClosure.
mk_MemVTableCallocFieldCallback :: C_MemVTableCallocFieldCallback -> IO (FunPtr C_MemVTableCallocFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MemVTableCallocFieldCallback.
noMemVTableCallocFieldCallback :: Maybe MemVTableCallocFieldCallback Source #
A convenience synonym for Nothing :: Maybe MemVTableCallocFieldCallback
wrap_MemVTableCallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableCallocFieldCallback)) -> MemVTableCallocFieldCallback -> C_MemVTableCallocFieldCallback Source #
Wrap a MemVTableCallocFieldCallback into a C_MemVTableCallocFieldCallback.
MemVTableFreeFieldCallback
type C_MemVTableFreeFieldCallback = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MemVTableFreeFieldCallback = Ptr () -> IO () Source #
No description available in the introspection data.
dynamic_MemVTableFreeFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableFreeFieldCallback -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemVTableFreeFieldCallback :: MonadIO m => MemVTableFreeFieldCallback -> m (GClosure C_MemVTableFreeFieldCallback) Source #
Wrap the callback into a GClosure.
mk_MemVTableFreeFieldCallback :: C_MemVTableFreeFieldCallback -> IO (FunPtr C_MemVTableFreeFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MemVTableFreeFieldCallback.
noMemVTableFreeFieldCallback :: Maybe MemVTableFreeFieldCallback Source #
A convenience synonym for Nothing :: Maybe MemVTableFreeFieldCallback
wrap_MemVTableFreeFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableFreeFieldCallback)) -> MemVTableFreeFieldCallback -> C_MemVTableFreeFieldCallback Source #
Wrap a MemVTableFreeFieldCallback into a C_MemVTableFreeFieldCallback.
MemVTableMallocFieldCallback
type C_MemVTableMallocFieldCallback = Word64 -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
type MemVTableMallocFieldCallback = Word64 -> IO (Ptr ()) Source #
No description available in the introspection data.
dynamic_MemVTableMallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableMallocFieldCallback -> Word64 -> m (Ptr ()) Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemVTableMallocFieldCallback :: MonadIO m => MemVTableMallocFieldCallback -> m (GClosure C_MemVTableMallocFieldCallback) Source #
Wrap the callback into a GClosure.
mk_MemVTableMallocFieldCallback :: C_MemVTableMallocFieldCallback -> IO (FunPtr C_MemVTableMallocFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MemVTableMallocFieldCallback.
noMemVTableMallocFieldCallback :: Maybe MemVTableMallocFieldCallback Source #
A convenience synonym for Nothing :: Maybe MemVTableMallocFieldCallback
wrap_MemVTableMallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableMallocFieldCallback)) -> MemVTableMallocFieldCallback -> C_MemVTableMallocFieldCallback Source #
Wrap a MemVTableMallocFieldCallback into a C_MemVTableMallocFieldCallback.
MemVTableReallocFieldCallback
type C_MemVTableReallocFieldCallback = Ptr () -> Word64 -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
type MemVTableReallocFieldCallback = Ptr () -> Word64 -> IO (Ptr ()) Source #
No description available in the introspection data.
dynamic_MemVTableReallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableReallocFieldCallback -> Ptr () -> Word64 -> m (Ptr ()) Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemVTableReallocFieldCallback :: MonadIO m => MemVTableReallocFieldCallback -> m (GClosure C_MemVTableReallocFieldCallback) Source #
Wrap the callback into a GClosure.
mk_MemVTableReallocFieldCallback :: C_MemVTableReallocFieldCallback -> IO (FunPtr C_MemVTableReallocFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MemVTableReallocFieldCallback.
noMemVTableReallocFieldCallback :: Maybe MemVTableReallocFieldCallback Source #
A convenience synonym for Nothing :: Maybe MemVTableReallocFieldCallback
wrap_MemVTableReallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableReallocFieldCallback)) -> MemVTableReallocFieldCallback -> C_MemVTableReallocFieldCallback Source #
Wrap a MemVTableReallocFieldCallback into a C_MemVTableReallocFieldCallback.
MemVTableTryMallocFieldCallback
type C_MemVTableTryMallocFieldCallback = Word64 -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
type MemVTableTryMallocFieldCallback = Word64 -> IO (Ptr ()) Source #
No description available in the introspection data.
dynamic_MemVTableTryMallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableTryMallocFieldCallback -> Word64 -> m (Ptr ()) Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemVTableTryMallocFieldCallback :: MonadIO m => MemVTableTryMallocFieldCallback -> m (GClosure C_MemVTableTryMallocFieldCallback) Source #
Wrap the callback into a GClosure.
mk_MemVTableTryMallocFieldCallback :: C_MemVTableTryMallocFieldCallback -> IO (FunPtr C_MemVTableTryMallocFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MemVTableTryMallocFieldCallback.
noMemVTableTryMallocFieldCallback :: Maybe MemVTableTryMallocFieldCallback Source #
A convenience synonym for Nothing :: Maybe MemVTableTryMallocFieldCallback
wrap_MemVTableTryMallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableTryMallocFieldCallback)) -> MemVTableTryMallocFieldCallback -> C_MemVTableTryMallocFieldCallback Source #
Wrap a MemVTableTryMallocFieldCallback into a C_MemVTableTryMallocFieldCallback.
MemVTableTryReallocFieldCallback
type C_MemVTableTryReallocFieldCallback = Ptr () -> Word64 -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
type MemVTableTryReallocFieldCallback = Ptr () -> Word64 -> IO (Ptr ()) Source #
No description available in the introspection data.
dynamic_MemVTableTryReallocFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_MemVTableTryReallocFieldCallback -> Ptr () -> Word64 -> m (Ptr ()) Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemVTableTryReallocFieldCallback :: MonadIO m => MemVTableTryReallocFieldCallback -> m (GClosure C_MemVTableTryReallocFieldCallback) Source #
Wrap the callback into a GClosure.
mk_MemVTableTryReallocFieldCallback :: C_MemVTableTryReallocFieldCallback -> IO (FunPtr C_MemVTableTryReallocFieldCallback) Source #
Generate a function pointer callable from C code, from a C_MemVTableTryReallocFieldCallback.
noMemVTableTryReallocFieldCallback :: Maybe MemVTableTryReallocFieldCallback Source #
A convenience synonym for Nothing :: Maybe MemVTableTryReallocFieldCallback
wrap_MemVTableTryReallocFieldCallback :: Maybe (Ptr (FunPtr C_MemVTableTryReallocFieldCallback)) -> MemVTableTryReallocFieldCallback -> C_MemVTableTryReallocFieldCallback Source #
NodeForeachFunc
type C_NodeForeachFunc = Ptr Node -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type NodeForeachFunc Source #
Arguments
| = Node | 
 | 
| -> Ptr () | 
 | 
| -> IO () | 
Specifies the type of function passed to g_node_children_foreach().
The function is called with each child node, together with the user
data passed to g_node_children_foreach().
dynamic_NodeForeachFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_NodeForeachFunc | |
| -> Node | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_NodeForeachFunc :: MonadIO m => NodeForeachFunc -> m (GClosure C_NodeForeachFunc) Source #
Wrap the callback into a GClosure.
mk_NodeForeachFunc :: C_NodeForeachFunc -> IO (FunPtr C_NodeForeachFunc) Source #
Generate a function pointer callable from C code, from a C_NodeForeachFunc.
noNodeForeachFunc :: Maybe NodeForeachFunc Source #
A convenience synonym for Nothing :: Maybe NodeForeachFunc
wrap_NodeForeachFunc :: Maybe (Ptr (FunPtr C_NodeForeachFunc)) -> NodeForeachFunc -> C_NodeForeachFunc Source #
Wrap a NodeForeachFunc into a C_NodeForeachFunc.
NodeTraverseFunc
type C_NodeTraverseFunc = Ptr Node -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type NodeTraverseFunc Source #
Arguments
| = Node | 
 | 
| -> Ptr () | 
 | 
| -> IO Bool | Returns:  | 
Specifies the type of function passed to g_node_traverse(). The
function is called with each of the nodes visited, together with the
user data passed to g_node_traverse(). If the function returns
True, then the traversal is stopped.
dynamic_NodeTraverseFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_NodeTraverseFunc | |
| -> Node | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | Returns:  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_NodeTraverseFunc :: MonadIO m => NodeTraverseFunc -> m (GClosure C_NodeTraverseFunc) Source #
Wrap the callback into a GClosure.
mk_NodeTraverseFunc :: C_NodeTraverseFunc -> IO (FunPtr C_NodeTraverseFunc) Source #
Generate a function pointer callable from C code, from a C_NodeTraverseFunc.
noNodeTraverseFunc :: Maybe NodeTraverseFunc Source #
A convenience synonym for Nothing :: Maybe NodeTraverseFunc
wrap_NodeTraverseFunc :: Maybe (Ptr (FunPtr C_NodeTraverseFunc)) -> NodeTraverseFunc -> C_NodeTraverseFunc Source #
Wrap a NodeTraverseFunc into a C_NodeTraverseFunc.
OptionArgFunc
type C_OptionArgFunc = CString -> CString -> Ptr () -> Ptr (Ptr GError) -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type OptionArgFunc Source #
Arguments
| = Text | 
 | 
| -> Text | 
 | 
| -> Ptr () | 
 | 
| -> IO () | Returns:  | 
The type of function to be passed as callback for OptionArgCallback
options.
dynamic_OptionArgFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_OptionArgFunc | |
| -> Text | 
 | 
| -> Text | 
 | 
| -> Ptr () | 
 | 
| -> m () | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_OptionArgFunc :: C_OptionArgFunc -> IO (FunPtr C_OptionArgFunc) Source #
Generate a function pointer callable from C code, from a C_OptionArgFunc.
noOptionArgFunc :: Maybe OptionArgFunc Source #
A convenience synonym for Nothing :: Maybe OptionArgFunc
OptionErrorFunc
type C_OptionErrorFunc = Ptr OptionContext -> Ptr OptionGroup -> Ptr () -> Ptr (Ptr GError) -> IO () Source #
Type for the callback on the (unwrapped) C side.
type OptionErrorFunc Source #
Arguments
| = OptionContext | 
 | 
| -> OptionGroup | 
 | 
| -> Ptr () | 
 | 
| -> IO () | (Can throw  | 
The type of function to be used as callback when a parse error occurs.
dynamic_OptionErrorFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_OptionErrorFunc | |
| -> OptionContext | 
 | 
| -> OptionGroup | 
 | 
| -> Ptr () | 
 | 
| -> m () | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_OptionErrorFunc :: C_OptionErrorFunc -> IO (FunPtr C_OptionErrorFunc) Source #
Generate a function pointer callable from C code, from a C_OptionErrorFunc.
noOptionErrorFunc :: Maybe OptionErrorFunc Source #
A convenience synonym for Nothing :: Maybe OptionErrorFunc
OptionParseFunc
type C_OptionParseFunc = Ptr OptionContext -> Ptr OptionGroup -> Ptr () -> Ptr (Ptr GError) -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type OptionParseFunc Source #
Arguments
| = OptionContext | 
 | 
| -> OptionGroup | 
 | 
| -> Ptr () | 
 | 
| -> IO () | Returns:  | 
The type of function that can be called before and after parsing.
dynamic_OptionParseFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_OptionParseFunc | |
| -> OptionContext | 
 | 
| -> OptionGroup | 
 | 
| -> Ptr () | 
 | 
| -> m () | (Can throw  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_OptionParseFunc :: C_OptionParseFunc -> IO (FunPtr C_OptionParseFunc) Source #
Generate a function pointer callable from C code, from a C_OptionParseFunc.
noOptionParseFunc :: Maybe OptionParseFunc Source #
A convenience synonym for Nothing :: Maybe OptionParseFunc
PollFunc
type C_PollFunc = Ptr PollFD -> Word32 -> Int32 -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
Arguments
| = PollFD | 
 | 
| -> Word32 | 
 | 
| -> Int32 | 
 | 
| -> IO Int32 | Returns: the number of  | 
Specifies the type of function passed to g_main_context_set_poll_func().
The semantics of the function should match those of the poll() system call.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_PollFunc | |
| -> PollFD | 
 | 
| -> Word32 | 
 | 
| -> Int32 | 
 | 
| -> m Int32 | Returns: the number of  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PollFunc :: MonadIO m => PollFunc -> m (GClosure C_PollFunc) Source #
Wrap the callback into a GClosure.
mk_PollFunc :: C_PollFunc -> IO (FunPtr C_PollFunc) Source #
Generate a function pointer callable from C code, from a C_PollFunc.
wrap_PollFunc :: Maybe (Ptr (FunPtr C_PollFunc)) -> PollFunc -> C_PollFunc Source #
Wrap a PollFunc into a C_PollFunc.
PrintFunc
type C_PrintFunc = CString -> IO () Source #
Type for the callback on the (unwrapped) C side.
Specifies the type of the print handler functions. These are called with the complete formatted string to output.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_PrintFunc | |
| -> Text | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PrintFunc :: MonadIO m => PrintFunc -> m (GClosure C_PrintFunc) Source #
Wrap the callback into a GClosure.
mk_PrintFunc :: C_PrintFunc -> IO (FunPtr C_PrintFunc) Source #
Generate a function pointer callable from C code, from a C_PrintFunc.
wrap_PrintFunc :: Maybe (Ptr (FunPtr C_PrintFunc)) -> PrintFunc -> C_PrintFunc Source #
Wrap a PrintFunc into a C_PrintFunc.
RegexEvalCallback
type C_RegexEvalCallback = Ptr MatchInfo -> Ptr String -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type RegexEvalCallback Source #
Arguments
| = MatchInfo | 
 | 
| -> String | 
 | 
| -> IO Bool | Returns:  | 
Specifies the type of the function passed to g_regex_replace_eval().
It is called for each occurrence of the pattern in the string passed
to g_regex_replace_eval(), and it should append the replacement to
result.
Since: 2.14
type RegexEvalCallback_WithClosures Source #
Arguments
| = MatchInfo | 
 | 
| -> String | 
 | 
| -> Ptr () | 
 | 
| -> IO Bool | Returns:  | 
Specifies the type of the function passed to g_regex_replace_eval().
It is called for each occurrence of the pattern in the string passed
to g_regex_replace_eval(), and it should append the replacement to
result.
Since: 2.14
drop_closures_RegexEvalCallback :: RegexEvalCallback -> RegexEvalCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_RegexEvalCallback Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_RegexEvalCallback | |
| -> MatchInfo | 
 | 
| -> String | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | Returns:  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_RegexEvalCallback :: MonadIO m => RegexEvalCallback -> m (GClosure C_RegexEvalCallback) Source #
Wrap the callback into a GClosure.
mk_RegexEvalCallback :: C_RegexEvalCallback -> IO (FunPtr C_RegexEvalCallback) Source #
Generate a function pointer callable from C code, from a C_RegexEvalCallback.
noRegexEvalCallback :: Maybe RegexEvalCallback Source #
A convenience synonym for Nothing :: Maybe RegexEvalCallback
noRegexEvalCallback_WithClosures :: Maybe RegexEvalCallback_WithClosures Source #
A convenience synonym for Nothing :: Maybe RegexEvalCallback_WithClosures
wrap_RegexEvalCallback :: Maybe (Ptr (FunPtr C_RegexEvalCallback)) -> RegexEvalCallback_WithClosures -> C_RegexEvalCallback Source #
Wrap a RegexEvalCallback into a C_RegexEvalCallback.
ScannerMsgFunc
type C_ScannerMsgFunc = Ptr Scanner -> CString -> CInt -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ScannerMsgFunc Source #
Arguments
| = Scanner | 
 | 
| -> Text | 
 | 
| -> Bool | 
 | 
| -> IO () | 
Specifies the type of the message handler function.
dynamic_ScannerMsgFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_ScannerMsgFunc | |
| -> Scanner | 
 | 
| -> Text | 
 | 
| -> Bool | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ScannerMsgFunc :: MonadIO m => ScannerMsgFunc -> m (GClosure C_ScannerMsgFunc) Source #
Wrap the callback into a GClosure.
mk_ScannerMsgFunc :: C_ScannerMsgFunc -> IO (FunPtr C_ScannerMsgFunc) Source #
Generate a function pointer callable from C code, from a C_ScannerMsgFunc.
noScannerMsgFunc :: Maybe ScannerMsgFunc Source #
A convenience synonym for Nothing :: Maybe ScannerMsgFunc
wrap_ScannerMsgFunc :: Maybe (Ptr (FunPtr C_ScannerMsgFunc)) -> ScannerMsgFunc -> C_ScannerMsgFunc Source #
Wrap a ScannerMsgFunc into a C_ScannerMsgFunc.
SequenceIterCompareFunc
type C_SequenceIterCompareFunc = Ptr SequenceIter -> Ptr SequenceIter -> Ptr () -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type SequenceIterCompareFunc Source #
Arguments
| = SequenceIter | 
 | 
| -> SequenceIter | 
 | 
| -> Ptr () | 
 | 
| -> IO Int32 | Returns: zero if the iterators are equal, a negative value if  | 
A SequenceIterCompareFunc is a function used to compare iterators.
It must return zero if the iterators compare equal, a negative value
if a comes before b, and a positive value if b comes before a.
dynamic_SequenceIterCompareFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_SequenceIterCompareFunc | |
| -> SequenceIter | 
 | 
| -> SequenceIter | 
 | 
| -> Ptr () | 
 | 
| -> m Int32 | Returns: zero if the iterators are equal, a negative value if  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SequenceIterCompareFunc :: MonadIO m => SequenceIterCompareFunc -> m (GClosure C_SequenceIterCompareFunc) Source #
Wrap the callback into a GClosure.
mk_SequenceIterCompareFunc :: C_SequenceIterCompareFunc -> IO (FunPtr C_SequenceIterCompareFunc) Source #
Generate a function pointer callable from C code, from a C_SequenceIterCompareFunc.
noSequenceIterCompareFunc :: Maybe SequenceIterCompareFunc Source #
A convenience synonym for Nothing :: Maybe SequenceIterCompareFunc
wrap_SequenceIterCompareFunc :: Maybe (Ptr (FunPtr C_SequenceIterCompareFunc)) -> SequenceIterCompareFunc -> C_SequenceIterCompareFunc Source #
Wrap a SequenceIterCompareFunc into a C_SequenceIterCompareFunc.
SourceCallbackFuncsRefFieldCallback
type C_SourceCallbackFuncsRefFieldCallback = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SourceCallbackFuncsRefFieldCallback = Ptr () -> IO () Source #
No description available in the introspection data.
dynamic_SourceCallbackFuncsRefFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceCallbackFuncsRefFieldCallback -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SourceCallbackFuncsRefFieldCallback :: MonadIO m => SourceCallbackFuncsRefFieldCallback -> m (GClosure C_SourceCallbackFuncsRefFieldCallback) Source #
Wrap the callback into a GClosure.
mk_SourceCallbackFuncsRefFieldCallback :: C_SourceCallbackFuncsRefFieldCallback -> IO (FunPtr C_SourceCallbackFuncsRefFieldCallback) Source #
Generate a function pointer callable from C code, from a C_SourceCallbackFuncsRefFieldCallback.
noSourceCallbackFuncsRefFieldCallback :: Maybe SourceCallbackFuncsRefFieldCallback Source #
A convenience synonym for Nothing :: Maybe SourceCallbackFuncsRefFieldCallback
wrap_SourceCallbackFuncsRefFieldCallback :: Maybe (Ptr (FunPtr C_SourceCallbackFuncsRefFieldCallback)) -> SourceCallbackFuncsRefFieldCallback -> C_SourceCallbackFuncsRefFieldCallback Source #
SourceCallbackFuncsUnrefFieldCallback
type C_SourceCallbackFuncsUnrefFieldCallback = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SourceCallbackFuncsUnrefFieldCallback = Ptr () -> IO () Source #
No description available in the introspection data.
dynamic_SourceCallbackFuncsUnrefFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceCallbackFuncsUnrefFieldCallback -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SourceCallbackFuncsUnrefFieldCallback :: MonadIO m => SourceCallbackFuncsUnrefFieldCallback -> m (GClosure C_SourceCallbackFuncsUnrefFieldCallback) Source #
Wrap the callback into a GClosure.
mk_SourceCallbackFuncsUnrefFieldCallback :: C_SourceCallbackFuncsUnrefFieldCallback -> IO (FunPtr C_SourceCallbackFuncsUnrefFieldCallback) Source #
Generate a function pointer callable from C code, from a C_SourceCallbackFuncsUnrefFieldCallback.
noSourceCallbackFuncsUnrefFieldCallback :: Maybe SourceCallbackFuncsUnrefFieldCallback Source #
A convenience synonym for Nothing :: Maybe SourceCallbackFuncsUnrefFieldCallback
wrap_SourceCallbackFuncsUnrefFieldCallback :: Maybe (Ptr (FunPtr C_SourceCallbackFuncsUnrefFieldCallback)) -> SourceCallbackFuncsUnrefFieldCallback -> C_SourceCallbackFuncsUnrefFieldCallback Source #
SourceDummyMarshal
type C_SourceDummyMarshal = IO () Source #
Type for the callback on the (unwrapped) C side.
type SourceDummyMarshal = IO () Source #
This is just a placeholder for GClosureMarshal,
which cannot be used here for dependency reasons.
dynamic_SourceDummyMarshal :: (HasCallStack, MonadIO m) => FunPtr C_SourceDummyMarshal -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SourceDummyMarshal :: MonadIO m => SourceDummyMarshal -> m (GClosure C_SourceDummyMarshal) Source #
Wrap the callback into a GClosure.
mk_SourceDummyMarshal :: C_SourceDummyMarshal -> IO (FunPtr C_SourceDummyMarshal) Source #
Generate a function pointer callable from C code, from a C_SourceDummyMarshal.
noSourceDummyMarshal :: Maybe SourceDummyMarshal Source #
A convenience synonym for Nothing :: Maybe SourceDummyMarshal
wrap_SourceDummyMarshal :: Maybe (Ptr (FunPtr C_SourceDummyMarshal)) -> SourceDummyMarshal -> C_SourceDummyMarshal Source #
Wrap a SourceDummyMarshal into a C_SourceDummyMarshal.
SourceFunc
type SourceFunc Source #
Arguments
| = IO Bool | Returns:  | 
Specifies the type of function passed to g_timeout_add(),
timeoutAdd, g_idle_add(), and idleAdd.
When calling sourceSetCallback, you may need to cast a function of a
different type to this type. Use G_SOURCE_FUNC() to avoid warnings about
incompatible function types.
type SourceFunc_WithClosures Source #
Arguments
| = Ptr () | 
 | 
| -> IO Bool | Returns:  | 
Specifies the type of function passed to g_timeout_add(),
timeoutAdd, g_idle_add(), and idleAdd.
When calling sourceSetCallback, you may need to cast a function of a
different type to this type. Use G_SOURCE_FUNC() to avoid warnings about
incompatible function types.
drop_closures_SourceFunc :: SourceFunc -> SourceFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_SourceFunc | |
| -> Ptr () | 
 | 
| -> m Bool | Returns:  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SourceFunc :: MonadIO m => SourceFunc -> m (GClosure C_SourceFunc) Source #
Wrap the callback into a GClosure.
mk_SourceFunc :: C_SourceFunc -> IO (FunPtr C_SourceFunc) Source #
Generate a function pointer callable from C code, from a C_SourceFunc.
noSourceFunc :: Maybe SourceFunc Source #
A convenience synonym for Nothing :: Maybe SourceFunc
noSourceFunc_WithClosures :: Maybe SourceFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe SourceFunc_WithClosures
wrap_SourceFunc :: Maybe (Ptr (FunPtr C_SourceFunc)) -> SourceFunc_WithClosures -> C_SourceFunc Source #
Wrap a SourceFunc into a C_SourceFunc.
SourceFuncsCheckFieldCallback
type C_SourceFuncsCheckFieldCallback = Ptr Source -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type SourceFuncsCheckFieldCallback = Source -> IO Bool Source #
No description available in the introspection data.
dynamic_SourceFuncsCheckFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceFuncsCheckFieldCallback -> Source -> m Bool Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SourceFuncsCheckFieldCallback :: MonadIO m => SourceFuncsCheckFieldCallback -> m (GClosure C_SourceFuncsCheckFieldCallback) Source #
Wrap the callback into a GClosure.
mk_SourceFuncsCheckFieldCallback :: C_SourceFuncsCheckFieldCallback -> IO (FunPtr C_SourceFuncsCheckFieldCallback) Source #
Generate a function pointer callable from C code, from a C_SourceFuncsCheckFieldCallback.
noSourceFuncsCheckFieldCallback :: Maybe SourceFuncsCheckFieldCallback Source #
A convenience synonym for Nothing :: Maybe SourceFuncsCheckFieldCallback
wrap_SourceFuncsCheckFieldCallback :: Maybe (Ptr (FunPtr C_SourceFuncsCheckFieldCallback)) -> SourceFuncsCheckFieldCallback -> C_SourceFuncsCheckFieldCallback Source #
Wrap a SourceFuncsCheckFieldCallback into a C_SourceFuncsCheckFieldCallback.
SourceFuncsFinalizeFieldCallback
type C_SourceFuncsFinalizeFieldCallback = Ptr Source -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SourceFuncsFinalizeFieldCallback = Source -> IO () Source #
No description available in the introspection data.
dynamic_SourceFuncsFinalizeFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceFuncsFinalizeFieldCallback -> Source -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SourceFuncsFinalizeFieldCallback :: MonadIO m => SourceFuncsFinalizeFieldCallback -> m (GClosure C_SourceFuncsFinalizeFieldCallback) Source #
Wrap the callback into a GClosure.
mk_SourceFuncsFinalizeFieldCallback :: C_SourceFuncsFinalizeFieldCallback -> IO (FunPtr C_SourceFuncsFinalizeFieldCallback) Source #
Generate a function pointer callable from C code, from a C_SourceFuncsFinalizeFieldCallback.
noSourceFuncsFinalizeFieldCallback :: Maybe SourceFuncsFinalizeFieldCallback Source #
A convenience synonym for Nothing :: Maybe SourceFuncsFinalizeFieldCallback
wrap_SourceFuncsFinalizeFieldCallback :: Maybe (Ptr (FunPtr C_SourceFuncsFinalizeFieldCallback)) -> SourceFuncsFinalizeFieldCallback -> C_SourceFuncsFinalizeFieldCallback Source #
SourceFuncsPrepareFieldCallback
type C_SourceFuncsPrepareFieldCallback = Ptr Source -> Int32 -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type SourceFuncsPrepareFieldCallback = Source -> Int32 -> IO Bool Source #
No description available in the introspection data.
dynamic_SourceFuncsPrepareFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_SourceFuncsPrepareFieldCallback -> Source -> Int32 -> m Bool Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SourceFuncsPrepareFieldCallback :: MonadIO m => SourceFuncsPrepareFieldCallback -> m (GClosure C_SourceFuncsPrepareFieldCallback) Source #
Wrap the callback into a GClosure.
mk_SourceFuncsPrepareFieldCallback :: C_SourceFuncsPrepareFieldCallback -> IO (FunPtr C_SourceFuncsPrepareFieldCallback) Source #
Generate a function pointer callable from C code, from a C_SourceFuncsPrepareFieldCallback.
noSourceFuncsPrepareFieldCallback :: Maybe SourceFuncsPrepareFieldCallback Source #
A convenience synonym for Nothing :: Maybe SourceFuncsPrepareFieldCallback
wrap_SourceFuncsPrepareFieldCallback :: Maybe (Ptr (FunPtr C_SourceFuncsPrepareFieldCallback)) -> SourceFuncsPrepareFieldCallback -> C_SourceFuncsPrepareFieldCallback Source #
Wrap a SourceFuncsPrepareFieldCallback into a C_SourceFuncsPrepareFieldCallback.
SpawnChildSetupFunc
type C_SpawnChildSetupFunc = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SpawnChildSetupFunc = IO () Source #
Specifies the type of the setup function passed to spawnAsync,
spawnSync and spawnAsyncWithPipes, which can, in very
limited ways, be used to affect the child's execution.
On POSIX platforms, the function is called in the child after GLib
has performed all the setup it plans to perform, but before calling
exec(). Actions taken in this function will only affect the child,
not the parent.
On Windows, the function is called in the parent. Its usefulness on Windows is thus questionable. In many cases executing the child setup function in the parent can have ill effects, and you should be very careful when porting software to Windows that uses child setup functions.
However, even on POSIX, you are extremely limited in what you can
safely do from a SpawnChildSetupFunc, because any mutexes that were
held by other threads in the parent process at the time of the fork()
will still be locked in the child process, and they will never be
unlocked (since the threads that held them don't exist in the child).
POSIX allows only async-signal-safe functions (see signal(7)) to be
called in the child between fork() and exec(), which drastically limits
the usefulness of child setup functions.
In particular, it is not safe to call any function which may
call malloc(), which includes POSIX functions such as setenv().
If you need to set up the child environment differently from
the parent, you should use getEnviron, environSetenv,
and environUnsetenv, and then pass the complete environment
list to the g_spawn... function.
type SpawnChildSetupFunc_WithClosures Source #
Specifies the type of the setup function passed to spawnAsync,
spawnSync and spawnAsyncWithPipes, which can, in very
limited ways, be used to affect the child's execution.
On POSIX platforms, the function is called in the child after GLib
has performed all the setup it plans to perform, but before calling
exec(). Actions taken in this function will only affect the child,
not the parent.
On Windows, the function is called in the parent. Its usefulness on Windows is thus questionable. In many cases executing the child setup function in the parent can have ill effects, and you should be very careful when porting software to Windows that uses child setup functions.
However, even on POSIX, you are extremely limited in what you can
safely do from a SpawnChildSetupFunc, because any mutexes that were
held by other threads in the parent process at the time of the fork()
will still be locked in the child process, and they will never be
unlocked (since the threads that held them don't exist in the child).
POSIX allows only async-signal-safe functions (see signal(7)) to be
called in the child between fork() and exec(), which drastically limits
the usefulness of child setup functions.
In particular, it is not safe to call any function which may
call malloc(), which includes POSIX functions such as setenv().
If you need to set up the child environment differently from
the parent, you should use getEnviron, environSetenv,
and environUnsetenv, and then pass the complete environment
list to the g_spawn... function.
drop_closures_SpawnChildSetupFunc :: SpawnChildSetupFunc -> SpawnChildSetupFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SpawnChildSetupFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_SpawnChildSetupFunc | |
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SpawnChildSetupFunc :: MonadIO m => SpawnChildSetupFunc -> m (GClosure C_SpawnChildSetupFunc) Source #
Wrap the callback into a GClosure.
mk_SpawnChildSetupFunc :: C_SpawnChildSetupFunc -> IO (FunPtr C_SpawnChildSetupFunc) Source #
Generate a function pointer callable from C code, from a C_SpawnChildSetupFunc.
noSpawnChildSetupFunc :: Maybe SpawnChildSetupFunc Source #
A convenience synonym for Nothing :: Maybe SpawnChildSetupFunc
noSpawnChildSetupFunc_WithClosures :: Maybe SpawnChildSetupFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe SpawnChildSetupFunc_WithClosures
wrap_SpawnChildSetupFunc :: Maybe (Ptr (FunPtr C_SpawnChildSetupFunc)) -> SpawnChildSetupFunc_WithClosures -> C_SpawnChildSetupFunc Source #
Wrap a SpawnChildSetupFunc into a C_SpawnChildSetupFunc.
TestDataFunc
type C_TestDataFunc = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TestDataFunc = IO () Source #
The type used for test case functions that take an extra pointer argument.
Since: 2.28
type TestDataFunc_WithClosures Source #
The type used for test case functions that take an extra pointer argument.
Since: 2.28
drop_closures_TestDataFunc :: TestDataFunc -> TestDataFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_TestDataFunc | |
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TestDataFunc :: MonadIO m => TestDataFunc -> m (GClosure C_TestDataFunc) Source #
Wrap the callback into a GClosure.
mk_TestDataFunc :: C_TestDataFunc -> IO (FunPtr C_TestDataFunc) Source #
Generate a function pointer callable from C code, from a C_TestDataFunc.
noTestDataFunc :: Maybe TestDataFunc Source #
A convenience synonym for Nothing :: Maybe TestDataFunc
noTestDataFunc_WithClosures :: Maybe TestDataFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe TestDataFunc_WithClosures
wrap_TestDataFunc :: Maybe (Ptr (FunPtr C_TestDataFunc)) -> TestDataFunc_WithClosures -> C_TestDataFunc Source #
Wrap a TestDataFunc into a C_TestDataFunc.
TestFixtureFunc
type C_TestFixtureFunc = Ptr () -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TestFixtureFunc Source #
The type used for functions that operate on test fixtures. This is used for the fixture setup and teardown functions as well as for the testcases themselves.
userData is a pointer to the data that was given when registering
the test case.
fixture will be a pointer to the area of memory allocated by the
test framework, of the size requested.  If the requested size was
zero then fixture will be equal to userData.
Since: 2.28
type TestFixtureFunc_WithClosures Source #
Arguments
| = Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO () | 
The type used for functions that operate on test fixtures. This is used for the fixture setup and teardown functions as well as for the testcases themselves.
userData is a pointer to the data that was given when registering
the test case.
fixture will be a pointer to the area of memory allocated by the
test framework, of the size requested.  If the requested size was
zero then fixture will be equal to userData.
Since: 2.28
drop_closures_TestFixtureFunc :: TestFixtureFunc -> TestFixtureFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TestFixtureFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_TestFixtureFunc | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m () | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TestFixtureFunc :: MonadIO m => TestFixtureFunc -> m (GClosure C_TestFixtureFunc) Source #
Wrap the callback into a GClosure.
mk_TestFixtureFunc :: C_TestFixtureFunc -> IO (FunPtr C_TestFixtureFunc) Source #
Generate a function pointer callable from C code, from a C_TestFixtureFunc.
noTestFixtureFunc :: Maybe TestFixtureFunc Source #
A convenience synonym for Nothing :: Maybe TestFixtureFunc
noTestFixtureFunc_WithClosures :: Maybe TestFixtureFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe TestFixtureFunc_WithClosures
wrap_TestFixtureFunc :: Maybe (Ptr (FunPtr C_TestFixtureFunc)) -> TestFixtureFunc_WithClosures -> C_TestFixtureFunc Source #
Wrap a TestFixtureFunc into a C_TestFixtureFunc.
TestFunc
type C_TestFunc = IO () Source #
Type for the callback on the (unwrapped) C side.
dynamic_TestFunc :: (HasCallStack, MonadIO m) => FunPtr C_TestFunc -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TestFunc :: MonadIO m => TestFunc -> m (GClosure C_TestFunc) Source #
Wrap the callback into a GClosure.
mk_TestFunc :: C_TestFunc -> IO (FunPtr C_TestFunc) Source #
Generate a function pointer callable from C code, from a C_TestFunc.
wrap_TestFunc :: Maybe (Ptr (FunPtr C_TestFunc)) -> TestFunc -> C_TestFunc Source #
Wrap a TestFunc into a C_TestFunc.
TestLogFatalFunc
type C_TestLogFatalFunc = CString -> CInt -> CString -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TestLogFatalFunc Source #
Arguments
| = Text | 
 | 
| -> [LogLevelFlags] | 
 | 
| -> Text | 
 | 
| -> IO Bool | 
Specifies the prototype of fatal log handler functions.
Since: 2.22
type TestLogFatalFunc_WithClosures Source #
Arguments
| = Text | 
 | 
| -> [LogLevelFlags] | 
 | 
| -> Text | 
 | 
| -> Ptr () | 
 | 
| -> IO Bool | 
Specifies the prototype of fatal log handler functions.
Since: 2.22
drop_closures_TestLogFatalFunc :: TestLogFatalFunc -> TestLogFatalFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TestLogFatalFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_TestLogFatalFunc | |
| -> Text | 
 | 
| -> [LogLevelFlags] | 
 | 
| -> Text | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TestLogFatalFunc :: MonadIO m => TestLogFatalFunc -> m (GClosure C_TestLogFatalFunc) Source #
Wrap the callback into a GClosure.
mk_TestLogFatalFunc :: C_TestLogFatalFunc -> IO (FunPtr C_TestLogFatalFunc) Source #
Generate a function pointer callable from C code, from a C_TestLogFatalFunc.
noTestLogFatalFunc :: Maybe TestLogFatalFunc Source #
A convenience synonym for Nothing :: Maybe TestLogFatalFunc
noTestLogFatalFunc_WithClosures :: Maybe TestLogFatalFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe TestLogFatalFunc_WithClosures
wrap_TestLogFatalFunc :: Maybe (Ptr (FunPtr C_TestLogFatalFunc)) -> TestLogFatalFunc_WithClosures -> C_TestLogFatalFunc Source #
Wrap a TestLogFatalFunc into a C_TestLogFatalFunc.
ThreadFunc
type ThreadFunc Source #
Arguments
| = Ptr () | 
 | 
| -> IO (Ptr ()) | Returns: the return value of the thread | 
Specifies the type of the func functions passed to g_thread_new()
or g_thread_try_new().
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_ThreadFunc | |
| -> Ptr () | 
 | 
| -> m (Ptr ()) | Returns: the return value of the thread | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ThreadFunc :: MonadIO m => ThreadFunc -> m (GClosure C_ThreadFunc) Source #
Wrap the callback into a GClosure.
mk_ThreadFunc :: C_ThreadFunc -> IO (FunPtr C_ThreadFunc) Source #
Generate a function pointer callable from C code, from a C_ThreadFunc.
noThreadFunc :: Maybe ThreadFunc Source #
A convenience synonym for Nothing :: Maybe ThreadFunc
wrap_ThreadFunc :: Maybe (Ptr (FunPtr C_ThreadFunc)) -> ThreadFunc -> C_ThreadFunc Source #
Wrap a ThreadFunc into a C_ThreadFunc.
TranslateFunc
type C_TranslateFunc = CString -> Ptr () -> IO CString Source #
Type for the callback on the (unwrapped) C side.
type TranslateFunc Source #
Arguments
| = Text | 
 | 
| -> Ptr () | 
 | 
| -> IO Text | Returns: a translation of the string for the current locale. The returned string is owned by GLib and must not be freed. | 
The type of functions which are used to translate user-visible strings, for <option>--help</option> output.
dynamic_TranslateFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_TranslateFunc | |
| -> Text | 
 | 
| -> Ptr () | 
 | 
| -> m Text | Returns: a translation of the string for the current locale. The returned string is owned by GLib and must not be freed. | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TranslateFunc :: MonadIO m => TranslateFunc -> m (GClosure C_TranslateFunc) Source #
Wrap the callback into a GClosure.
mk_TranslateFunc :: C_TranslateFunc -> IO (FunPtr C_TranslateFunc) Source #
Generate a function pointer callable from C code, from a C_TranslateFunc.
noTranslateFunc :: Maybe TranslateFunc Source #
A convenience synonym for Nothing :: Maybe TranslateFunc
wrap_TranslateFunc :: Maybe (Ptr (FunPtr C_TranslateFunc)) -> TranslateFunc -> C_TranslateFunc Source #
Wrap a TranslateFunc into a C_TranslateFunc.
TraverseFunc
type C_TraverseFunc = Ptr () -> Ptr () -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type TraverseFunc Source #
Arguments
| = Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> IO Bool | Returns:  | 
Specifies the type of function passed to g_tree_traverse(). It is
passed the key and value of each node, together with the userData
parameter passed to g_tree_traverse(). If the function returns
True, the traversal is stopped.
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_TraverseFunc | |
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | Returns:  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TraverseFunc :: MonadIO m => TraverseFunc -> m (GClosure C_TraverseFunc) Source #
Wrap the callback into a GClosure.
mk_TraverseFunc :: C_TraverseFunc -> IO (FunPtr C_TraverseFunc) Source #
Generate a function pointer callable from C code, from a C_TraverseFunc.
noTraverseFunc :: Maybe TraverseFunc Source #
A convenience synonym for Nothing :: Maybe TraverseFunc
wrap_TraverseFunc :: Maybe (Ptr (FunPtr C_TraverseFunc)) -> TraverseFunc -> C_TraverseFunc Source #
Wrap a TraverseFunc into a C_TraverseFunc.
UnixFDSourceFunc
type C_UnixFDSourceFunc = Int32 -> CUInt -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type UnixFDSourceFunc Source #
Arguments
| = Int32 | 
 | 
| -> [IOCondition] | 
 | 
| -> IO Bool | Returns:  | 
The type of functions to be called when a UNIX fd watch source triggers.
type UnixFDSourceFunc_WithClosures Source #
Arguments
| = Int32 | 
 | 
| -> [IOCondition] | 
 | 
| -> Ptr () | 
 | 
| -> IO Bool | Returns:  | 
The type of functions to be called when a UNIX fd watch source triggers.
drop_closures_UnixFDSourceFunc :: UnixFDSourceFunc -> UnixFDSourceFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UnixFDSourceFunc Source #
Arguments
| :: (HasCallStack, MonadIO m) | |
| => FunPtr C_UnixFDSourceFunc | |
| -> Int32 | 
 | 
| -> [IOCondition] | 
 | 
| -> Ptr () | 
 | 
| -> m Bool | Returns:  | 
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UnixFDSourceFunc :: MonadIO m => UnixFDSourceFunc -> m (GClosure C_UnixFDSourceFunc) Source #
Wrap the callback into a GClosure.
mk_UnixFDSourceFunc :: C_UnixFDSourceFunc -> IO (FunPtr C_UnixFDSourceFunc) Source #
Generate a function pointer callable from C code, from a C_UnixFDSourceFunc.
noUnixFDSourceFunc :: Maybe UnixFDSourceFunc Source #
A convenience synonym for Nothing :: Maybe UnixFDSourceFunc
noUnixFDSourceFunc_WithClosures :: Maybe UnixFDSourceFunc_WithClosures Source #
A convenience synonym for Nothing :: Maybe UnixFDSourceFunc_WithClosures
wrap_UnixFDSourceFunc :: Maybe (Ptr (FunPtr C_UnixFDSourceFunc)) -> UnixFDSourceFunc_WithClosures -> C_UnixFDSourceFunc Source #
Wrap a UnixFDSourceFunc into a C_UnixFDSourceFunc.
VoidFunc
type C_VoidFunc = IO () Source #
Type for the callback on the (unwrapped) C side.
type VoidFunc = IO () Source #
Declares a type of function which takes no arguments
and has no return value. It is used to specify the type
function passed to atexit.
dynamic_VoidFunc :: (HasCallStack, MonadIO m) => FunPtr C_VoidFunc -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VoidFunc :: MonadIO m => VoidFunc -> m (GClosure C_VoidFunc) Source #
Wrap the callback into a GClosure.
mk_VoidFunc :: C_VoidFunc -> IO (FunPtr C_VoidFunc) Source #
Generate a function pointer callable from C code, from a C_VoidFunc.
wrap_VoidFunc :: Maybe (Ptr (FunPtr C_VoidFunc)) -> VoidFunc -> C_VoidFunc Source #
Wrap a VoidFunc into a C_VoidFunc.