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 |
- Signals
- BufferForeachMetaFunc
- BufferListFunc
- BusFunc
- BusSyncHandler
- CapsFilterMapFunc
- CapsForeachFunc
- CapsMapFunc
- ClockCallback
- ControlBindingConvert
- ControlSourceGetValue
- ControlSourceGetValueArray
- DebugFuncPtr
- ElementCallAsyncFunc
- ElementForeachPadFunc
- IteratorCopyFunction
- IteratorFoldFunction
- IteratorForeachFunction
- IteratorFreeFunction
- IteratorItemFunction
- IteratorNextFunction
- IteratorResyncFunction
- LogFunction
- MemoryCopyFunction
- MemoryIsSpanFunction
- MemoryMapFullFunction
- MemoryMapFunction
- MemoryShareFunction
- MemoryUnmapFullFunction
- MemoryUnmapFunction
- MetaFreeFunction
- MetaInitFunction
- MetaTransformFunction
- MiniObjectDisposeFunction
- MiniObjectFreeFunction
- MiniObjectNotify
- PadActivateFunction
- PadActivateModeFunction
- PadChainFunction
- PadChainListFunction
- PadEventFullFunction
- PadEventFunction
- PadForwardFunction
- PadGetRangeFunction
- PadIterIntLinkFunction
- PadLinkFunction
- PadProbeCallback
- PadQueryFunction
- PadStickyEventsForeachFunction
- PadUnlinkFunction
- PluginFeatureFilter
- PluginFilter
- PluginInitFullFunc
- PluginInitFunc
- PromiseChangeFunc
- StructureFilterMapFunc
- StructureForeachFunc
- StructureMapFunc
- TagForeachFunc
- TagMergeFunc
- TaskFunction
- TaskPoolFunction
- TaskThreadFunc
- TypeFindFunction
- TypeFindGetLengthFieldCallback
- TypeFindPeekFieldCallback
- TypeFindSuggestFieldCallback
- ValueCompareFunc
- ValueDeserializeFunc
- ValueSerializeFunc
Synopsis
- type BufferForeachMetaFunc = Buffer -> IO (Bool, Maybe Meta)
- type BufferForeachMetaFunc_WithClosures = Buffer -> Ptr () -> IO (Bool, Maybe Meta)
- type C_BufferForeachMetaFunc = Ptr Buffer -> Ptr (Ptr Meta) -> Ptr () -> IO CInt
- drop_closures_BufferForeachMetaFunc :: BufferForeachMetaFunc -> BufferForeachMetaFunc_WithClosures
- dynamic_BufferForeachMetaFunc :: (HasCallStack, MonadIO m) => FunPtr C_BufferForeachMetaFunc -> Buffer -> Ptr () -> m (Bool, Maybe Meta)
- genClosure_BufferForeachMetaFunc :: MonadIO m => BufferForeachMetaFunc -> m (GClosure C_BufferForeachMetaFunc)
- mk_BufferForeachMetaFunc :: C_BufferForeachMetaFunc -> IO (FunPtr C_BufferForeachMetaFunc)
- noBufferForeachMetaFunc :: Maybe BufferForeachMetaFunc
- noBufferForeachMetaFunc_WithClosures :: Maybe BufferForeachMetaFunc_WithClosures
- wrap_BufferForeachMetaFunc :: Maybe (Ptr (FunPtr C_BufferForeachMetaFunc)) -> BufferForeachMetaFunc_WithClosures -> C_BufferForeachMetaFunc
- type BufferListFunc = Word32 -> IO (Bool, Maybe Buffer)
- type BufferListFunc_WithClosures = Word32 -> Ptr () -> IO (Bool, Maybe Buffer)
- type C_BufferListFunc = Ptr (Ptr Buffer) -> Word32 -> Ptr () -> IO CInt
- drop_closures_BufferListFunc :: BufferListFunc -> BufferListFunc_WithClosures
- dynamic_BufferListFunc :: (HasCallStack, MonadIO m) => FunPtr C_BufferListFunc -> Word32 -> Ptr () -> m (Bool, Maybe Buffer)
- genClosure_BufferListFunc :: MonadIO m => BufferListFunc -> m (GClosure C_BufferListFunc)
- mk_BufferListFunc :: C_BufferListFunc -> IO (FunPtr C_BufferListFunc)
- noBufferListFunc :: Maybe BufferListFunc
- noBufferListFunc_WithClosures :: Maybe BufferListFunc_WithClosures
- wrap_BufferListFunc :: Maybe (Ptr (FunPtr C_BufferListFunc)) -> BufferListFunc_WithClosures -> C_BufferListFunc
- type BusFunc = Bus -> Message -> IO Bool
- type BusFunc_WithClosures = Bus -> Message -> Ptr () -> IO Bool
- type C_BusFunc = Ptr Bus -> Ptr Message -> Ptr () -> IO CInt
- drop_closures_BusFunc :: BusFunc -> BusFunc_WithClosures
- dynamic_BusFunc :: (HasCallStack, MonadIO m, IsBus a) => FunPtr C_BusFunc -> a -> Message -> Ptr () -> m Bool
- genClosure_BusFunc :: MonadIO m => BusFunc -> m (GClosure C_BusFunc)
- mk_BusFunc :: C_BusFunc -> IO (FunPtr C_BusFunc)
- noBusFunc :: Maybe BusFunc
- noBusFunc_WithClosures :: Maybe BusFunc_WithClosures
- wrap_BusFunc :: Maybe (Ptr (FunPtr C_BusFunc)) -> BusFunc_WithClosures -> C_BusFunc
- type BusSyncHandler = Bus -> Message -> IO BusSyncReply
- type BusSyncHandler_WithClosures = Bus -> Message -> Ptr () -> IO BusSyncReply
- type C_BusSyncHandler = Ptr Bus -> Ptr Message -> Ptr () -> IO CUInt
- drop_closures_BusSyncHandler :: BusSyncHandler -> BusSyncHandler_WithClosures
- dynamic_BusSyncHandler :: (HasCallStack, MonadIO m, IsBus a) => FunPtr C_BusSyncHandler -> a -> Message -> Ptr () -> m BusSyncReply
- genClosure_BusSyncHandler :: MonadIO m => BusSyncHandler -> m (GClosure C_BusSyncHandler)
- mk_BusSyncHandler :: C_BusSyncHandler -> IO (FunPtr C_BusSyncHandler)
- noBusSyncHandler :: Maybe BusSyncHandler
- noBusSyncHandler_WithClosures :: Maybe BusSyncHandler_WithClosures
- wrap_BusSyncHandler :: Maybe (Ptr (FunPtr C_BusSyncHandler)) -> BusSyncHandler_WithClosures -> C_BusSyncHandler
- type C_CapsFilterMapFunc = Ptr CapsFeatures -> Ptr Structure -> Ptr () -> IO CInt
- type CapsFilterMapFunc = CapsFeatures -> Structure -> IO Bool
- type CapsFilterMapFunc_WithClosures = CapsFeatures -> Structure -> Ptr () -> IO Bool
- drop_closures_CapsFilterMapFunc :: CapsFilterMapFunc -> CapsFilterMapFunc_WithClosures
- dynamic_CapsFilterMapFunc :: (HasCallStack, MonadIO m) => FunPtr C_CapsFilterMapFunc -> CapsFeatures -> Structure -> Ptr () -> m Bool
- genClosure_CapsFilterMapFunc :: MonadIO m => CapsFilterMapFunc -> m (GClosure C_CapsFilterMapFunc)
- mk_CapsFilterMapFunc :: C_CapsFilterMapFunc -> IO (FunPtr C_CapsFilterMapFunc)
- noCapsFilterMapFunc :: Maybe CapsFilterMapFunc
- noCapsFilterMapFunc_WithClosures :: Maybe CapsFilterMapFunc_WithClosures
- wrap_CapsFilterMapFunc :: Maybe (Ptr (FunPtr C_CapsFilterMapFunc)) -> CapsFilterMapFunc_WithClosures -> C_CapsFilterMapFunc
- type C_CapsForeachFunc = Ptr CapsFeatures -> Ptr Structure -> Ptr () -> IO CInt
- type CapsForeachFunc = CapsFeatures -> Structure -> IO Bool
- type CapsForeachFunc_WithClosures = CapsFeatures -> Structure -> Ptr () -> IO Bool
- drop_closures_CapsForeachFunc :: CapsForeachFunc -> CapsForeachFunc_WithClosures
- dynamic_CapsForeachFunc :: (HasCallStack, MonadIO m) => FunPtr C_CapsForeachFunc -> CapsFeatures -> Structure -> Ptr () -> m Bool
- genClosure_CapsForeachFunc :: MonadIO m => CapsForeachFunc -> m (GClosure C_CapsForeachFunc)
- mk_CapsForeachFunc :: C_CapsForeachFunc -> IO (FunPtr C_CapsForeachFunc)
- noCapsForeachFunc :: Maybe CapsForeachFunc
- noCapsForeachFunc_WithClosures :: Maybe CapsForeachFunc_WithClosures
- wrap_CapsForeachFunc :: Maybe (Ptr (FunPtr C_CapsForeachFunc)) -> CapsForeachFunc_WithClosures -> C_CapsForeachFunc
- type C_CapsMapFunc = Ptr CapsFeatures -> Ptr Structure -> Ptr () -> IO CInt
- type CapsMapFunc = CapsFeatures -> Structure -> IO Bool
- type CapsMapFunc_WithClosures = CapsFeatures -> Structure -> Ptr () -> IO Bool
- drop_closures_CapsMapFunc :: CapsMapFunc -> CapsMapFunc_WithClosures
- dynamic_CapsMapFunc :: (HasCallStack, MonadIO m) => FunPtr C_CapsMapFunc -> CapsFeatures -> Structure -> Ptr () -> m Bool
- genClosure_CapsMapFunc :: MonadIO m => CapsMapFunc -> m (GClosure C_CapsMapFunc)
- mk_CapsMapFunc :: C_CapsMapFunc -> IO (FunPtr C_CapsMapFunc)
- noCapsMapFunc :: Maybe CapsMapFunc
- noCapsMapFunc_WithClosures :: Maybe CapsMapFunc_WithClosures
- wrap_CapsMapFunc :: Maybe (Ptr (FunPtr C_CapsMapFunc)) -> CapsMapFunc_WithClosures -> C_CapsMapFunc
- type C_ClockCallback = Ptr Clock -> Word64 -> Ptr () -> Ptr () -> IO CInt
- type ClockCallback = Clock -> Word64 -> Ptr () -> IO Bool
- type ClockCallback_WithClosures = Clock -> Word64 -> Ptr () -> Ptr () -> IO Bool
- drop_closures_ClockCallback :: ClockCallback -> ClockCallback_WithClosures
- dynamic_ClockCallback :: (HasCallStack, MonadIO m, IsClock a) => FunPtr C_ClockCallback -> a -> Word64 -> Ptr () -> Ptr () -> m Bool
- genClosure_ClockCallback :: MonadIO m => ClockCallback -> m (GClosure C_ClockCallback)
- mk_ClockCallback :: C_ClockCallback -> IO (FunPtr C_ClockCallback)
- noClockCallback :: Maybe ClockCallback
- noClockCallback_WithClosures :: Maybe ClockCallback_WithClosures
- wrap_ClockCallback :: Maybe (Ptr (FunPtr C_ClockCallback)) -> ClockCallback_WithClosures -> C_ClockCallback
- type C_ControlBindingConvert = Ptr ControlBinding -> CDouble -> Ptr GValue -> IO ()
- type ControlBindingConvert = ControlBinding -> Double -> GValue -> IO ()
- dynamic_ControlBindingConvert :: (HasCallStack, MonadIO m, IsControlBinding a) => FunPtr C_ControlBindingConvert -> a -> Double -> GValue -> m ()
- genClosure_ControlBindingConvert :: MonadIO m => ControlBindingConvert -> m (GClosure C_ControlBindingConvert)
- mk_ControlBindingConvert :: C_ControlBindingConvert -> IO (FunPtr C_ControlBindingConvert)
- noControlBindingConvert :: Maybe ControlBindingConvert
- wrap_ControlBindingConvert :: Maybe (Ptr (FunPtr C_ControlBindingConvert)) -> ControlBindingConvert -> C_ControlBindingConvert
- type C_ControlSourceGetValue = Ptr ControlSource -> Word64 -> CDouble -> IO CInt
- type ControlSourceGetValue = ControlSource -> Word64 -> Double -> IO Bool
- dynamic_ControlSourceGetValue :: (HasCallStack, MonadIO m, IsControlSource a) => FunPtr C_ControlSourceGetValue -> a -> Word64 -> Double -> m Bool
- genClosure_ControlSourceGetValue :: MonadIO m => ControlSourceGetValue -> m (GClosure C_ControlSourceGetValue)
- mk_ControlSourceGetValue :: C_ControlSourceGetValue -> IO (FunPtr C_ControlSourceGetValue)
- noControlSourceGetValue :: Maybe ControlSourceGetValue
- wrap_ControlSourceGetValue :: Maybe (Ptr (FunPtr C_ControlSourceGetValue)) -> ControlSourceGetValue -> C_ControlSourceGetValue
- type C_ControlSourceGetValueArray = Ptr ControlSource -> Word64 -> Word64 -> Word32 -> CDouble -> IO CInt
- type ControlSourceGetValueArray = ControlSource -> Word64 -> Word64 -> Word32 -> Double -> IO Bool
- dynamic_ControlSourceGetValueArray :: (HasCallStack, MonadIO m, IsControlSource a) => FunPtr C_ControlSourceGetValueArray -> a -> Word64 -> Word64 -> Word32 -> Double -> m Bool
- genClosure_ControlSourceGetValueArray :: MonadIO m => ControlSourceGetValueArray -> m (GClosure C_ControlSourceGetValueArray)
- mk_ControlSourceGetValueArray :: C_ControlSourceGetValueArray -> IO (FunPtr C_ControlSourceGetValueArray)
- noControlSourceGetValueArray :: Maybe ControlSourceGetValueArray
- wrap_ControlSourceGetValueArray :: Maybe (Ptr (FunPtr C_ControlSourceGetValueArray)) -> ControlSourceGetValueArray -> C_ControlSourceGetValueArray
- type C_DebugFuncPtr = IO ()
- type DebugFuncPtr = IO ()
- dynamic_DebugFuncPtr :: (HasCallStack, MonadIO m) => FunPtr C_DebugFuncPtr -> m ()
- genClosure_DebugFuncPtr :: MonadIO m => DebugFuncPtr -> m (GClosure C_DebugFuncPtr)
- mk_DebugFuncPtr :: C_DebugFuncPtr -> IO (FunPtr C_DebugFuncPtr)
- noDebugFuncPtr :: Maybe DebugFuncPtr
- wrap_DebugFuncPtr :: Maybe (Ptr (FunPtr C_DebugFuncPtr)) -> DebugFuncPtr -> C_DebugFuncPtr
- type C_ElementCallAsyncFunc = Ptr Element -> Ptr () -> IO ()
- type ElementCallAsyncFunc = Element -> IO ()
- type ElementCallAsyncFunc_WithClosures = Element -> Ptr () -> IO ()
- drop_closures_ElementCallAsyncFunc :: ElementCallAsyncFunc -> ElementCallAsyncFunc_WithClosures
- dynamic_ElementCallAsyncFunc :: (HasCallStack, MonadIO m, IsElement a) => FunPtr C_ElementCallAsyncFunc -> a -> Ptr () -> m ()
- genClosure_ElementCallAsyncFunc :: MonadIO m => ElementCallAsyncFunc -> m (GClosure C_ElementCallAsyncFunc)
- mk_ElementCallAsyncFunc :: C_ElementCallAsyncFunc -> IO (FunPtr C_ElementCallAsyncFunc)
- noElementCallAsyncFunc :: Maybe ElementCallAsyncFunc
- noElementCallAsyncFunc_WithClosures :: Maybe ElementCallAsyncFunc_WithClosures
- wrap_ElementCallAsyncFunc :: Maybe (Ptr (FunPtr C_ElementCallAsyncFunc)) -> ElementCallAsyncFunc_WithClosures -> C_ElementCallAsyncFunc
- type C_ElementForeachPadFunc = Ptr Element -> Ptr Pad -> Ptr () -> IO CInt
- type ElementForeachPadFunc = Element -> Pad -> IO Bool
- type ElementForeachPadFunc_WithClosures = Element -> Pad -> Ptr () -> IO Bool
- drop_closures_ElementForeachPadFunc :: ElementForeachPadFunc -> ElementForeachPadFunc_WithClosures
- dynamic_ElementForeachPadFunc :: (HasCallStack, MonadIO m, IsElement a, IsPad b) => FunPtr C_ElementForeachPadFunc -> a -> b -> Ptr () -> m Bool
- genClosure_ElementForeachPadFunc :: MonadIO m => ElementForeachPadFunc -> m (GClosure C_ElementForeachPadFunc)
- mk_ElementForeachPadFunc :: C_ElementForeachPadFunc -> IO (FunPtr C_ElementForeachPadFunc)
- noElementForeachPadFunc :: Maybe ElementForeachPadFunc
- noElementForeachPadFunc_WithClosures :: Maybe ElementForeachPadFunc_WithClosures
- wrap_ElementForeachPadFunc :: Maybe (Ptr (FunPtr C_ElementForeachPadFunc)) -> ElementForeachPadFunc_WithClosures -> C_ElementForeachPadFunc
- type C_IteratorCopyFunction = Ptr Iterator -> Ptr Iterator -> IO ()
- type IteratorCopyFunction = Iterator -> Iterator -> IO ()
- dynamic_IteratorCopyFunction :: (HasCallStack, MonadIO m) => FunPtr C_IteratorCopyFunction -> Iterator -> Iterator -> m ()
- genClosure_IteratorCopyFunction :: MonadIO m => IteratorCopyFunction -> m (GClosure C_IteratorCopyFunction)
- mk_IteratorCopyFunction :: C_IteratorCopyFunction -> IO (FunPtr C_IteratorCopyFunction)
- noIteratorCopyFunction :: Maybe IteratorCopyFunction
- wrap_IteratorCopyFunction :: Maybe (Ptr (FunPtr C_IteratorCopyFunction)) -> IteratorCopyFunction -> C_IteratorCopyFunction
- type C_IteratorFoldFunction = Ptr GValue -> Ptr GValue -> Ptr () -> IO CInt
- type IteratorFoldFunction = GValue -> GValue -> IO Bool
- type IteratorFoldFunction_WithClosures = GValue -> GValue -> Ptr () -> IO Bool
- drop_closures_IteratorFoldFunction :: IteratorFoldFunction -> IteratorFoldFunction_WithClosures
- dynamic_IteratorFoldFunction :: (HasCallStack, MonadIO m) => FunPtr C_IteratorFoldFunction -> GValue -> GValue -> Ptr () -> m Bool
- genClosure_IteratorFoldFunction :: MonadIO m => IteratorFoldFunction -> m (GClosure C_IteratorFoldFunction)
- mk_IteratorFoldFunction :: C_IteratorFoldFunction -> IO (FunPtr C_IteratorFoldFunction)
- noIteratorFoldFunction :: Maybe IteratorFoldFunction
- noIteratorFoldFunction_WithClosures :: Maybe IteratorFoldFunction_WithClosures
- wrap_IteratorFoldFunction :: Maybe (Ptr (FunPtr C_IteratorFoldFunction)) -> IteratorFoldFunction_WithClosures -> C_IteratorFoldFunction
- type C_IteratorForeachFunction = Ptr GValue -> Ptr () -> IO ()
- type IteratorForeachFunction = GValue -> IO ()
- type IteratorForeachFunction_WithClosures = GValue -> Ptr () -> IO ()
- drop_closures_IteratorForeachFunction :: IteratorForeachFunction -> IteratorForeachFunction_WithClosures
- dynamic_IteratorForeachFunction :: (HasCallStack, MonadIO m) => FunPtr C_IteratorForeachFunction -> GValue -> Ptr () -> m ()
- genClosure_IteratorForeachFunction :: MonadIO m => IteratorForeachFunction -> m (GClosure C_IteratorForeachFunction)
- mk_IteratorForeachFunction :: C_IteratorForeachFunction -> IO (FunPtr C_IteratorForeachFunction)
- noIteratorForeachFunction :: Maybe IteratorForeachFunction
- noIteratorForeachFunction_WithClosures :: Maybe IteratorForeachFunction_WithClosures
- wrap_IteratorForeachFunction :: Maybe (Ptr (FunPtr C_IteratorForeachFunction)) -> IteratorForeachFunction_WithClosures -> C_IteratorForeachFunction
- type C_IteratorFreeFunction = Ptr Iterator -> IO ()
- type IteratorFreeFunction = Iterator -> IO ()
- dynamic_IteratorFreeFunction :: (HasCallStack, MonadIO m) => FunPtr C_IteratorFreeFunction -> Iterator -> m ()
- genClosure_IteratorFreeFunction :: MonadIO m => IteratorFreeFunction -> m (GClosure C_IteratorFreeFunction)
- mk_IteratorFreeFunction :: C_IteratorFreeFunction -> IO (FunPtr C_IteratorFreeFunction)
- noIteratorFreeFunction :: Maybe IteratorFreeFunction
- wrap_IteratorFreeFunction :: Maybe (Ptr (FunPtr C_IteratorFreeFunction)) -> IteratorFreeFunction -> C_IteratorFreeFunction
- type C_IteratorItemFunction = Ptr Iterator -> Ptr GValue -> IO CUInt
- type IteratorItemFunction = Iterator -> GValue -> IO IteratorItem
- dynamic_IteratorItemFunction :: (HasCallStack, MonadIO m) => FunPtr C_IteratorItemFunction -> Iterator -> GValue -> m IteratorItem
- genClosure_IteratorItemFunction :: MonadIO m => IteratorItemFunction -> m (GClosure C_IteratorItemFunction)
- mk_IteratorItemFunction :: C_IteratorItemFunction -> IO (FunPtr C_IteratorItemFunction)
- noIteratorItemFunction :: Maybe IteratorItemFunction
- wrap_IteratorItemFunction :: Maybe (Ptr (FunPtr C_IteratorItemFunction)) -> IteratorItemFunction -> C_IteratorItemFunction
- type C_IteratorNextFunction = Ptr Iterator -> Ptr GValue -> IO CUInt
- type IteratorNextFunction = Iterator -> GValue -> IO IteratorResult
- dynamic_IteratorNextFunction :: (HasCallStack, MonadIO m) => FunPtr C_IteratorNextFunction -> Iterator -> GValue -> m IteratorResult
- genClosure_IteratorNextFunction :: MonadIO m => IteratorNextFunction -> m (GClosure C_IteratorNextFunction)
- mk_IteratorNextFunction :: C_IteratorNextFunction -> IO (FunPtr C_IteratorNextFunction)
- noIteratorNextFunction :: Maybe IteratorNextFunction
- wrap_IteratorNextFunction :: Maybe (Ptr (FunPtr C_IteratorNextFunction)) -> IteratorNextFunction -> C_IteratorNextFunction
- type C_IteratorResyncFunction = Ptr Iterator -> IO ()
- type IteratorResyncFunction = Iterator -> IO ()
- dynamic_IteratorResyncFunction :: (HasCallStack, MonadIO m) => FunPtr C_IteratorResyncFunction -> Iterator -> m ()
- genClosure_IteratorResyncFunction :: MonadIO m => IteratorResyncFunction -> m (GClosure C_IteratorResyncFunction)
- mk_IteratorResyncFunction :: C_IteratorResyncFunction -> IO (FunPtr C_IteratorResyncFunction)
- noIteratorResyncFunction :: Maybe IteratorResyncFunction
- wrap_IteratorResyncFunction :: Maybe (Ptr (FunPtr C_IteratorResyncFunction)) -> IteratorResyncFunction -> C_IteratorResyncFunction
- type C_LogFunction = Ptr DebugCategory -> CUInt -> CString -> CString -> Int32 -> Ptr Object -> Ptr DebugMessage -> Ptr () -> IO ()
- type LogFunction = DebugCategory -> DebugLevel -> Text -> Text -> Int32 -> Object -> DebugMessage -> IO ()
- type LogFunction_WithClosures = DebugCategory -> DebugLevel -> Text -> Text -> Int32 -> Object -> DebugMessage -> Ptr () -> IO ()
- drop_closures_LogFunction :: LogFunction -> LogFunction_WithClosures
- dynamic_LogFunction :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_LogFunction -> DebugCategory -> DebugLevel -> Text -> Text -> Int32 -> a -> DebugMessage -> Ptr () -> m ()
- genClosure_LogFunction :: MonadIO m => LogFunction -> m (GClosure C_LogFunction)
- mk_LogFunction :: C_LogFunction -> IO (FunPtr C_LogFunction)
- noLogFunction :: Maybe LogFunction
- noLogFunction_WithClosures :: Maybe LogFunction_WithClosures
- wrap_LogFunction :: Maybe (Ptr (FunPtr C_LogFunction)) -> LogFunction_WithClosures -> C_LogFunction
- type C_MemoryCopyFunction = Ptr Memory -> Int64 -> Int64 -> IO (Ptr Memory)
- type MemoryCopyFunction = Memory -> Int64 -> Int64 -> IO Memory
- dynamic_MemoryCopyFunction :: (HasCallStack, MonadIO m) => FunPtr C_MemoryCopyFunction -> Memory -> Int64 -> Int64 -> m Memory
- genClosure_MemoryCopyFunction :: MonadIO m => MemoryCopyFunction -> m (GClosure C_MemoryCopyFunction)
- mk_MemoryCopyFunction :: C_MemoryCopyFunction -> IO (FunPtr C_MemoryCopyFunction)
- noMemoryCopyFunction :: Maybe MemoryCopyFunction
- wrap_MemoryCopyFunction :: Maybe (Ptr (FunPtr C_MemoryCopyFunction)) -> MemoryCopyFunction -> C_MemoryCopyFunction
- type C_MemoryIsSpanFunction = Ptr Memory -> Ptr Memory -> Word64 -> IO CInt
- type MemoryIsSpanFunction = Memory -> Memory -> Word64 -> IO Bool
- dynamic_MemoryIsSpanFunction :: (HasCallStack, MonadIO m) => FunPtr C_MemoryIsSpanFunction -> Memory -> Memory -> Word64 -> m Bool
- genClosure_MemoryIsSpanFunction :: MonadIO m => MemoryIsSpanFunction -> m (GClosure C_MemoryIsSpanFunction)
- mk_MemoryIsSpanFunction :: C_MemoryIsSpanFunction -> IO (FunPtr C_MemoryIsSpanFunction)
- noMemoryIsSpanFunction :: Maybe MemoryIsSpanFunction
- wrap_MemoryIsSpanFunction :: Maybe (Ptr (FunPtr C_MemoryIsSpanFunction)) -> MemoryIsSpanFunction -> C_MemoryIsSpanFunction
- type C_MemoryMapFullFunction = Ptr Memory -> Ptr MapInfo -> Word64 -> IO (Ptr ())
- type MemoryMapFullFunction = Memory -> MapInfo -> Word64 -> IO (Ptr ())
- dynamic_MemoryMapFullFunction :: (HasCallStack, MonadIO m) => FunPtr C_MemoryMapFullFunction -> Memory -> MapInfo -> Word64 -> m (Ptr ())
- genClosure_MemoryMapFullFunction :: MonadIO m => MemoryMapFullFunction -> m (GClosure C_MemoryMapFullFunction)
- mk_MemoryMapFullFunction :: C_MemoryMapFullFunction -> IO (FunPtr C_MemoryMapFullFunction)
- noMemoryMapFullFunction :: Maybe MemoryMapFullFunction
- wrap_MemoryMapFullFunction :: Maybe (Ptr (FunPtr C_MemoryMapFullFunction)) -> MemoryMapFullFunction -> C_MemoryMapFullFunction
- type C_MemoryMapFunction = Ptr Memory -> Word64 -> CUInt -> IO (Ptr ())
- type MemoryMapFunction = Memory -> Word64 -> [MapFlags] -> IO (Ptr ())
- dynamic_MemoryMapFunction :: (HasCallStack, MonadIO m) => FunPtr C_MemoryMapFunction -> Memory -> Word64 -> [MapFlags] -> m (Ptr ())
- genClosure_MemoryMapFunction :: MonadIO m => MemoryMapFunction -> m (GClosure C_MemoryMapFunction)
- mk_MemoryMapFunction :: C_MemoryMapFunction -> IO (FunPtr C_MemoryMapFunction)
- noMemoryMapFunction :: Maybe MemoryMapFunction
- wrap_MemoryMapFunction :: Maybe (Ptr (FunPtr C_MemoryMapFunction)) -> MemoryMapFunction -> C_MemoryMapFunction
- type C_MemoryShareFunction = Ptr Memory -> Int64 -> Int64 -> IO (Ptr Memory)
- type MemoryShareFunction = Memory -> Int64 -> Int64 -> IO Memory
- dynamic_MemoryShareFunction :: (HasCallStack, MonadIO m) => FunPtr C_MemoryShareFunction -> Memory -> Int64 -> Int64 -> m Memory
- genClosure_MemoryShareFunction :: MonadIO m => MemoryShareFunction -> m (GClosure C_MemoryShareFunction)
- mk_MemoryShareFunction :: C_MemoryShareFunction -> IO (FunPtr C_MemoryShareFunction)
- noMemoryShareFunction :: Maybe MemoryShareFunction
- wrap_MemoryShareFunction :: Maybe (Ptr (FunPtr C_MemoryShareFunction)) -> MemoryShareFunction -> C_MemoryShareFunction
- type C_MemoryUnmapFullFunction = Ptr Memory -> Ptr MapInfo -> IO ()
- type MemoryUnmapFullFunction = Memory -> MapInfo -> IO ()
- dynamic_MemoryUnmapFullFunction :: (HasCallStack, MonadIO m) => FunPtr C_MemoryUnmapFullFunction -> Memory -> MapInfo -> m ()
- genClosure_MemoryUnmapFullFunction :: MonadIO m => MemoryUnmapFullFunction -> m (GClosure C_MemoryUnmapFullFunction)
- mk_MemoryUnmapFullFunction :: C_MemoryUnmapFullFunction -> IO (FunPtr C_MemoryUnmapFullFunction)
- noMemoryUnmapFullFunction :: Maybe MemoryUnmapFullFunction
- wrap_MemoryUnmapFullFunction :: Maybe (Ptr (FunPtr C_MemoryUnmapFullFunction)) -> MemoryUnmapFullFunction -> C_MemoryUnmapFullFunction
- type C_MemoryUnmapFunction = Ptr Memory -> IO ()
- type MemoryUnmapFunction = Memory -> IO ()
- dynamic_MemoryUnmapFunction :: (HasCallStack, MonadIO m) => FunPtr C_MemoryUnmapFunction -> Memory -> m ()
- genClosure_MemoryUnmapFunction :: MonadIO m => MemoryUnmapFunction -> m (GClosure C_MemoryUnmapFunction)
- mk_MemoryUnmapFunction :: C_MemoryUnmapFunction -> IO (FunPtr C_MemoryUnmapFunction)
- noMemoryUnmapFunction :: Maybe MemoryUnmapFunction
- wrap_MemoryUnmapFunction :: Maybe (Ptr (FunPtr C_MemoryUnmapFunction)) -> MemoryUnmapFunction -> C_MemoryUnmapFunction
- type C_MetaFreeFunction = Ptr Meta -> Ptr Buffer -> IO ()
- type MetaFreeFunction = Meta -> Buffer -> IO ()
- dynamic_MetaFreeFunction :: (HasCallStack, MonadIO m) => FunPtr C_MetaFreeFunction -> Meta -> Buffer -> m ()
- genClosure_MetaFreeFunction :: MonadIO m => MetaFreeFunction -> m (GClosure C_MetaFreeFunction)
- mk_MetaFreeFunction :: C_MetaFreeFunction -> IO (FunPtr C_MetaFreeFunction)
- noMetaFreeFunction :: Maybe MetaFreeFunction
- wrap_MetaFreeFunction :: Maybe (Ptr (FunPtr C_MetaFreeFunction)) -> MetaFreeFunction -> C_MetaFreeFunction
- type C_MetaInitFunction = Ptr Meta -> Ptr () -> Ptr Buffer -> IO CInt
- type MetaInitFunction = Meta -> Ptr () -> Buffer -> IO Bool
- dynamic_MetaInitFunction :: (HasCallStack, MonadIO m) => FunPtr C_MetaInitFunction -> Meta -> Ptr () -> Buffer -> m Bool
- genClosure_MetaInitFunction :: MonadIO m => MetaInitFunction -> m (GClosure C_MetaInitFunction)
- mk_MetaInitFunction :: C_MetaInitFunction -> IO (FunPtr C_MetaInitFunction)
- noMetaInitFunction :: Maybe MetaInitFunction
- wrap_MetaInitFunction :: Maybe (Ptr (FunPtr C_MetaInitFunction)) -> MetaInitFunction -> C_MetaInitFunction
- type C_MetaTransformFunction = Ptr Buffer -> Ptr Meta -> Ptr Buffer -> Word32 -> Ptr () -> IO CInt
- type MetaTransformFunction = Buffer -> Meta -> Buffer -> Word32 -> Ptr () -> IO Bool
- dynamic_MetaTransformFunction :: (HasCallStack, MonadIO m) => FunPtr C_MetaTransformFunction -> Buffer -> Meta -> Buffer -> Word32 -> Ptr () -> m Bool
- genClosure_MetaTransformFunction :: MonadIO m => MetaTransformFunction -> m (GClosure C_MetaTransformFunction)
- mk_MetaTransformFunction :: C_MetaTransformFunction -> IO (FunPtr C_MetaTransformFunction)
- noMetaTransformFunction :: Maybe MetaTransformFunction
- wrap_MetaTransformFunction :: Maybe (Ptr (FunPtr C_MetaTransformFunction)) -> MetaTransformFunction -> C_MetaTransformFunction
- type C_MiniObjectDisposeFunction = Ptr MiniObject -> IO CInt
- type MiniObjectDisposeFunction = MiniObject -> IO Bool
- dynamic_MiniObjectDisposeFunction :: (HasCallStack, MonadIO m) => FunPtr C_MiniObjectDisposeFunction -> MiniObject -> m Bool
- genClosure_MiniObjectDisposeFunction :: MonadIO m => MiniObjectDisposeFunction -> m (GClosure C_MiniObjectDisposeFunction)
- mk_MiniObjectDisposeFunction :: C_MiniObjectDisposeFunction -> IO (FunPtr C_MiniObjectDisposeFunction)
- noMiniObjectDisposeFunction :: Maybe MiniObjectDisposeFunction
- wrap_MiniObjectDisposeFunction :: Maybe (Ptr (FunPtr C_MiniObjectDisposeFunction)) -> MiniObjectDisposeFunction -> C_MiniObjectDisposeFunction
- type C_MiniObjectFreeFunction = Ptr MiniObject -> IO ()
- type MiniObjectFreeFunction = MiniObject -> IO ()
- dynamic_MiniObjectFreeFunction :: (HasCallStack, MonadIO m) => FunPtr C_MiniObjectFreeFunction -> MiniObject -> m ()
- genClosure_MiniObjectFreeFunction :: MonadIO m => MiniObjectFreeFunction -> m (GClosure C_MiniObjectFreeFunction)
- mk_MiniObjectFreeFunction :: C_MiniObjectFreeFunction -> IO (FunPtr C_MiniObjectFreeFunction)
- noMiniObjectFreeFunction :: Maybe MiniObjectFreeFunction
- wrap_MiniObjectFreeFunction :: Maybe (Ptr (FunPtr C_MiniObjectFreeFunction)) -> MiniObjectFreeFunction -> C_MiniObjectFreeFunction
- type C_MiniObjectNotify = Ptr () -> Ptr MiniObject -> IO ()
- type MiniObjectNotify = MiniObject -> IO ()
- type MiniObjectNotify_WithClosures = Ptr () -> MiniObject -> IO ()
- drop_closures_MiniObjectNotify :: MiniObjectNotify -> MiniObjectNotify_WithClosures
- dynamic_MiniObjectNotify :: (HasCallStack, MonadIO m) => FunPtr C_MiniObjectNotify -> Ptr () -> MiniObject -> m ()
- genClosure_MiniObjectNotify :: MonadIO m => MiniObjectNotify -> m (GClosure C_MiniObjectNotify)
- mk_MiniObjectNotify :: C_MiniObjectNotify -> IO (FunPtr C_MiniObjectNotify)
- noMiniObjectNotify :: Maybe MiniObjectNotify
- noMiniObjectNotify_WithClosures :: Maybe MiniObjectNotify_WithClosures
- wrap_MiniObjectNotify :: Maybe (Ptr (FunPtr C_MiniObjectNotify)) -> MiniObjectNotify_WithClosures -> C_MiniObjectNotify
- type C_PadActivateFunction = Ptr Pad -> Ptr Object -> IO CInt
- type PadActivateFunction = Pad -> Object -> IO Bool
- dynamic_PadActivateFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadActivateFunction -> a -> b -> m Bool
- genClosure_PadActivateFunction :: MonadIO m => PadActivateFunction -> m (GClosure C_PadActivateFunction)
- mk_PadActivateFunction :: C_PadActivateFunction -> IO (FunPtr C_PadActivateFunction)
- noPadActivateFunction :: Maybe PadActivateFunction
- wrap_PadActivateFunction :: Maybe (Ptr (FunPtr C_PadActivateFunction)) -> PadActivateFunction -> C_PadActivateFunction
- type C_PadActivateModeFunction = Ptr Pad -> Ptr Object -> CUInt -> CInt -> IO CInt
- type PadActivateModeFunction = Pad -> Object -> PadMode -> Bool -> IO Bool
- dynamic_PadActivateModeFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadActivateModeFunction -> a -> b -> PadMode -> Bool -> m Bool
- genClosure_PadActivateModeFunction :: MonadIO m => PadActivateModeFunction -> m (GClosure C_PadActivateModeFunction)
- mk_PadActivateModeFunction :: C_PadActivateModeFunction -> IO (FunPtr C_PadActivateModeFunction)
- noPadActivateModeFunction :: Maybe PadActivateModeFunction
- wrap_PadActivateModeFunction :: Maybe (Ptr (FunPtr C_PadActivateModeFunction)) -> PadActivateModeFunction -> C_PadActivateModeFunction
- type C_PadChainFunction = Ptr Pad -> Ptr Object -> Ptr Buffer -> IO CInt
- type PadChainFunction = Pad -> Maybe Object -> Buffer -> IO FlowReturn
- dynamic_PadChainFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadChainFunction -> a -> Maybe b -> Buffer -> m FlowReturn
- genClosure_PadChainFunction :: MonadIO m => PadChainFunction -> m (GClosure C_PadChainFunction)
- mk_PadChainFunction :: C_PadChainFunction -> IO (FunPtr C_PadChainFunction)
- noPadChainFunction :: Maybe PadChainFunction
- wrap_PadChainFunction :: Maybe (Ptr (FunPtr C_PadChainFunction)) -> PadChainFunction -> C_PadChainFunction
- type C_PadChainListFunction = Ptr Pad -> Ptr Object -> Ptr BufferList -> IO CInt
- type PadChainListFunction = Pad -> Maybe Object -> BufferList -> IO FlowReturn
- dynamic_PadChainListFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadChainListFunction -> a -> Maybe b -> BufferList -> m FlowReturn
- genClosure_PadChainListFunction :: MonadIO m => PadChainListFunction -> m (GClosure C_PadChainListFunction)
- mk_PadChainListFunction :: C_PadChainListFunction -> IO (FunPtr C_PadChainListFunction)
- noPadChainListFunction :: Maybe PadChainListFunction
- wrap_PadChainListFunction :: Maybe (Ptr (FunPtr C_PadChainListFunction)) -> PadChainListFunction -> C_PadChainListFunction
- type C_PadEventFullFunction = Ptr Pad -> Ptr Object -> Ptr Event -> IO CInt
- type PadEventFullFunction = Pad -> Maybe Object -> Event -> IO FlowReturn
- dynamic_PadEventFullFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadEventFullFunction -> a -> Maybe b -> Event -> m FlowReturn
- genClosure_PadEventFullFunction :: MonadIO m => PadEventFullFunction -> m (GClosure C_PadEventFullFunction)
- mk_PadEventFullFunction :: C_PadEventFullFunction -> IO (FunPtr C_PadEventFullFunction)
- noPadEventFullFunction :: Maybe PadEventFullFunction
- wrap_PadEventFullFunction :: Maybe (Ptr (FunPtr C_PadEventFullFunction)) -> PadEventFullFunction -> C_PadEventFullFunction
- type C_PadEventFunction = Ptr Pad -> Ptr Object -> Ptr Event -> IO CInt
- type PadEventFunction = Pad -> Maybe Object -> Event -> IO Bool
- dynamic_PadEventFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadEventFunction -> a -> Maybe b -> Event -> m Bool
- genClosure_PadEventFunction :: MonadIO m => PadEventFunction -> m (GClosure C_PadEventFunction)
- mk_PadEventFunction :: C_PadEventFunction -> IO (FunPtr C_PadEventFunction)
- noPadEventFunction :: Maybe PadEventFunction
- wrap_PadEventFunction :: Maybe (Ptr (FunPtr C_PadEventFunction)) -> PadEventFunction -> C_PadEventFunction
- type C_PadForwardFunction = Ptr Pad -> Ptr () -> IO CInt
- type PadForwardFunction = Pad -> IO Bool
- type PadForwardFunction_WithClosures = Pad -> Ptr () -> IO Bool
- drop_closures_PadForwardFunction :: PadForwardFunction -> PadForwardFunction_WithClosures
- dynamic_PadForwardFunction :: (HasCallStack, MonadIO m, IsPad a) => FunPtr C_PadForwardFunction -> a -> Ptr () -> m Bool
- genClosure_PadForwardFunction :: MonadIO m => PadForwardFunction -> m (GClosure C_PadForwardFunction)
- mk_PadForwardFunction :: C_PadForwardFunction -> IO (FunPtr C_PadForwardFunction)
- noPadForwardFunction :: Maybe PadForwardFunction
- noPadForwardFunction_WithClosures :: Maybe PadForwardFunction_WithClosures
- wrap_PadForwardFunction :: Maybe (Ptr (FunPtr C_PadForwardFunction)) -> PadForwardFunction_WithClosures -> C_PadForwardFunction
- type C_PadGetRangeFunction = Ptr Pad -> Ptr Object -> Word64 -> Word32 -> Ptr Buffer -> IO CInt
- type PadGetRangeFunction = Pad -> Maybe Object -> Word64 -> Word32 -> Buffer -> IO FlowReturn
- dynamic_PadGetRangeFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadGetRangeFunction -> a -> Maybe b -> Word64 -> Word32 -> Buffer -> m FlowReturn
- genClosure_PadGetRangeFunction :: MonadIO m => PadGetRangeFunction -> m (GClosure C_PadGetRangeFunction)
- mk_PadGetRangeFunction :: C_PadGetRangeFunction -> IO (FunPtr C_PadGetRangeFunction)
- noPadGetRangeFunction :: Maybe PadGetRangeFunction
- wrap_PadGetRangeFunction :: Maybe (Ptr (FunPtr C_PadGetRangeFunction)) -> PadGetRangeFunction -> C_PadGetRangeFunction
- type C_PadIterIntLinkFunction = Ptr Pad -> Ptr Object -> IO (Ptr Iterator)
- type PadIterIntLinkFunction = Pad -> Maybe Object -> IO Iterator
- dynamic_PadIterIntLinkFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadIterIntLinkFunction -> a -> Maybe b -> m Iterator
- genClosure_PadIterIntLinkFunction :: MonadIO m => PadIterIntLinkFunction -> m (GClosure C_PadIterIntLinkFunction)
- mk_PadIterIntLinkFunction :: C_PadIterIntLinkFunction -> IO (FunPtr C_PadIterIntLinkFunction)
- noPadIterIntLinkFunction :: Maybe PadIterIntLinkFunction
- wrap_PadIterIntLinkFunction :: Maybe (Ptr (FunPtr C_PadIterIntLinkFunction)) -> PadIterIntLinkFunction -> C_PadIterIntLinkFunction
- type C_PadLinkFunction = Ptr Pad -> Ptr Object -> Ptr Pad -> IO CInt
- type PadLinkFunction = Pad -> Maybe Object -> Pad -> IO PadLinkReturn
- dynamic_PadLinkFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b, IsPad c) => FunPtr C_PadLinkFunction -> a -> Maybe b -> c -> m PadLinkReturn
- genClosure_PadLinkFunction :: MonadIO m => PadLinkFunction -> m (GClosure C_PadLinkFunction)
- mk_PadLinkFunction :: C_PadLinkFunction -> IO (FunPtr C_PadLinkFunction)
- noPadLinkFunction :: Maybe PadLinkFunction
- wrap_PadLinkFunction :: Maybe (Ptr (FunPtr C_PadLinkFunction)) -> PadLinkFunction -> C_PadLinkFunction
- type C_PadProbeCallback = Ptr Pad -> Ptr PadProbeInfo -> Ptr () -> IO CUInt
- type PadProbeCallback = Pad -> PadProbeInfo -> IO PadProbeReturn
- type PadProbeCallback_WithClosures = Pad -> PadProbeInfo -> Ptr () -> IO PadProbeReturn
- drop_closures_PadProbeCallback :: PadProbeCallback -> PadProbeCallback_WithClosures
- dynamic_PadProbeCallback :: (HasCallStack, MonadIO m, IsPad a) => FunPtr C_PadProbeCallback -> a -> PadProbeInfo -> Ptr () -> m PadProbeReturn
- genClosure_PadProbeCallback :: MonadIO m => PadProbeCallback -> m (GClosure C_PadProbeCallback)
- mk_PadProbeCallback :: C_PadProbeCallback -> IO (FunPtr C_PadProbeCallback)
- noPadProbeCallback :: Maybe PadProbeCallback
- noPadProbeCallback_WithClosures :: Maybe PadProbeCallback_WithClosures
- wrap_PadProbeCallback :: Maybe (Ptr (FunPtr C_PadProbeCallback)) -> PadProbeCallback_WithClosures -> C_PadProbeCallback
- type C_PadQueryFunction = Ptr Pad -> Ptr Object -> Ptr Query -> IO CInt
- type PadQueryFunction = Pad -> Maybe Object -> Query -> IO Bool
- dynamic_PadQueryFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadQueryFunction -> a -> Maybe b -> Query -> m Bool
- genClosure_PadQueryFunction :: MonadIO m => PadQueryFunction -> m (GClosure C_PadQueryFunction)
- mk_PadQueryFunction :: C_PadQueryFunction -> IO (FunPtr C_PadQueryFunction)
- noPadQueryFunction :: Maybe PadQueryFunction
- wrap_PadQueryFunction :: Maybe (Ptr (FunPtr C_PadQueryFunction)) -> PadQueryFunction -> C_PadQueryFunction
- type C_PadStickyEventsForeachFunction = Ptr Pad -> Ptr Event -> Ptr () -> IO CInt
- type PadStickyEventsForeachFunction = Pad -> Maybe Event -> IO Bool
- type PadStickyEventsForeachFunction_WithClosures = Pad -> Maybe Event -> Ptr () -> IO Bool
- drop_closures_PadStickyEventsForeachFunction :: PadStickyEventsForeachFunction -> PadStickyEventsForeachFunction_WithClosures
- dynamic_PadStickyEventsForeachFunction :: (HasCallStack, MonadIO m, IsPad a) => FunPtr C_PadStickyEventsForeachFunction -> a -> Maybe Event -> Ptr () -> m Bool
- genClosure_PadStickyEventsForeachFunction :: MonadIO m => PadStickyEventsForeachFunction -> m (GClosure C_PadStickyEventsForeachFunction)
- mk_PadStickyEventsForeachFunction :: C_PadStickyEventsForeachFunction -> IO (FunPtr C_PadStickyEventsForeachFunction)
- noPadStickyEventsForeachFunction :: Maybe PadStickyEventsForeachFunction
- noPadStickyEventsForeachFunction_WithClosures :: Maybe PadStickyEventsForeachFunction_WithClosures
- wrap_PadStickyEventsForeachFunction :: Maybe (Ptr (FunPtr C_PadStickyEventsForeachFunction)) -> PadStickyEventsForeachFunction_WithClosures -> C_PadStickyEventsForeachFunction
- type C_PadUnlinkFunction = Ptr Pad -> Ptr Object -> IO ()
- type PadUnlinkFunction = Pad -> Maybe Object -> IO ()
- dynamic_PadUnlinkFunction :: (HasCallStack, MonadIO m, IsPad a, IsObject b) => FunPtr C_PadUnlinkFunction -> a -> Maybe b -> m ()
- genClosure_PadUnlinkFunction :: MonadIO m => PadUnlinkFunction -> m (GClosure C_PadUnlinkFunction)
- mk_PadUnlinkFunction :: C_PadUnlinkFunction -> IO (FunPtr C_PadUnlinkFunction)
- noPadUnlinkFunction :: Maybe PadUnlinkFunction
- wrap_PadUnlinkFunction :: Maybe (Ptr (FunPtr C_PadUnlinkFunction)) -> PadUnlinkFunction -> C_PadUnlinkFunction
- type C_PluginFeatureFilter = Ptr PluginFeature -> Ptr () -> IO CInt
- type PluginFeatureFilter = PluginFeature -> IO Bool
- type PluginFeatureFilter_WithClosures = PluginFeature -> Ptr () -> IO Bool
- drop_closures_PluginFeatureFilter :: PluginFeatureFilter -> PluginFeatureFilter_WithClosures
- dynamic_PluginFeatureFilter :: (HasCallStack, MonadIO m, IsPluginFeature a) => FunPtr C_PluginFeatureFilter -> a -> Ptr () -> m Bool
- genClosure_PluginFeatureFilter :: MonadIO m => PluginFeatureFilter -> m (GClosure C_PluginFeatureFilter)
- mk_PluginFeatureFilter :: C_PluginFeatureFilter -> IO (FunPtr C_PluginFeatureFilter)
- noPluginFeatureFilter :: Maybe PluginFeatureFilter
- noPluginFeatureFilter_WithClosures :: Maybe PluginFeatureFilter_WithClosures
- wrap_PluginFeatureFilter :: Maybe (Ptr (FunPtr C_PluginFeatureFilter)) -> PluginFeatureFilter_WithClosures -> C_PluginFeatureFilter
- type C_PluginFilter = Ptr Plugin -> Ptr () -> IO CInt
- type PluginFilter = Plugin -> IO Bool
- type PluginFilter_WithClosures = Plugin -> Ptr () -> IO Bool
- drop_closures_PluginFilter :: PluginFilter -> PluginFilter_WithClosures
- dynamic_PluginFilter :: (HasCallStack, MonadIO m, IsPlugin a) => FunPtr C_PluginFilter -> a -> Ptr () -> m Bool
- genClosure_PluginFilter :: MonadIO m => PluginFilter -> m (GClosure C_PluginFilter)
- mk_PluginFilter :: C_PluginFilter -> IO (FunPtr C_PluginFilter)
- noPluginFilter :: Maybe PluginFilter
- noPluginFilter_WithClosures :: Maybe PluginFilter_WithClosures
- wrap_PluginFilter :: Maybe (Ptr (FunPtr C_PluginFilter)) -> PluginFilter_WithClosures -> C_PluginFilter
- type C_PluginInitFullFunc = Ptr Plugin -> Ptr () -> IO CInt
- type PluginInitFullFunc = Plugin -> IO Bool
- type PluginInitFullFunc_WithClosures = Plugin -> Ptr () -> IO Bool
- drop_closures_PluginInitFullFunc :: PluginInitFullFunc -> PluginInitFullFunc_WithClosures
- dynamic_PluginInitFullFunc :: (HasCallStack, MonadIO m, IsPlugin a) => FunPtr C_PluginInitFullFunc -> a -> Ptr () -> m Bool
- genClosure_PluginInitFullFunc :: MonadIO m => PluginInitFullFunc -> m (GClosure C_PluginInitFullFunc)
- mk_PluginInitFullFunc :: C_PluginInitFullFunc -> IO (FunPtr C_PluginInitFullFunc)
- noPluginInitFullFunc :: Maybe PluginInitFullFunc
- noPluginInitFullFunc_WithClosures :: Maybe PluginInitFullFunc_WithClosures
- wrap_PluginInitFullFunc :: Maybe (Ptr (FunPtr C_PluginInitFullFunc)) -> PluginInitFullFunc_WithClosures -> C_PluginInitFullFunc
- type C_PluginInitFunc = Ptr Plugin -> IO CInt
- type PluginInitFunc = Plugin -> IO Bool
- dynamic_PluginInitFunc :: (HasCallStack, MonadIO m, IsPlugin a) => FunPtr C_PluginInitFunc -> a -> m Bool
- genClosure_PluginInitFunc :: MonadIO m => PluginInitFunc -> m (GClosure C_PluginInitFunc)
- mk_PluginInitFunc :: C_PluginInitFunc -> IO (FunPtr C_PluginInitFunc)
- noPluginInitFunc :: Maybe PluginInitFunc
- wrap_PluginInitFunc :: Maybe (Ptr (FunPtr C_PluginInitFunc)) -> PluginInitFunc -> C_PluginInitFunc
- type C_PromiseChangeFunc = Ptr Promise -> Ptr () -> IO ()
- type PromiseChangeFunc = Promise -> IO ()
- type PromiseChangeFunc_WithClosures = Promise -> Ptr () -> IO ()
- drop_closures_PromiseChangeFunc :: PromiseChangeFunc -> PromiseChangeFunc_WithClosures
- dynamic_PromiseChangeFunc :: (HasCallStack, MonadIO m) => FunPtr C_PromiseChangeFunc -> Promise -> Ptr () -> m ()
- genClosure_PromiseChangeFunc :: MonadIO m => PromiseChangeFunc -> m (GClosure C_PromiseChangeFunc)
- mk_PromiseChangeFunc :: C_PromiseChangeFunc -> IO (FunPtr C_PromiseChangeFunc)
- noPromiseChangeFunc :: Maybe PromiseChangeFunc
- noPromiseChangeFunc_WithClosures :: Maybe PromiseChangeFunc_WithClosures
- wrap_PromiseChangeFunc :: Maybe (Ptr (FunPtr C_PromiseChangeFunc)) -> PromiseChangeFunc_WithClosures -> C_PromiseChangeFunc
- type C_StructureFilterMapFunc = Word32 -> Ptr GValue -> Ptr () -> IO CInt
- type StructureFilterMapFunc = Word32 -> GValue -> IO Bool
- type StructureFilterMapFunc_WithClosures = Word32 -> GValue -> Ptr () -> IO Bool
- drop_closures_StructureFilterMapFunc :: StructureFilterMapFunc -> StructureFilterMapFunc_WithClosures
- dynamic_StructureFilterMapFunc :: (HasCallStack, MonadIO m) => FunPtr C_StructureFilterMapFunc -> Word32 -> GValue -> Ptr () -> m Bool
- genClosure_StructureFilterMapFunc :: MonadIO m => StructureFilterMapFunc -> m (GClosure C_StructureFilterMapFunc)
- mk_StructureFilterMapFunc :: C_StructureFilterMapFunc -> IO (FunPtr C_StructureFilterMapFunc)
- noStructureFilterMapFunc :: Maybe StructureFilterMapFunc
- noStructureFilterMapFunc_WithClosures :: Maybe StructureFilterMapFunc_WithClosures
- wrap_StructureFilterMapFunc :: Maybe (Ptr (FunPtr C_StructureFilterMapFunc)) -> StructureFilterMapFunc_WithClosures -> C_StructureFilterMapFunc
- type C_StructureForeachFunc = Word32 -> Ptr GValue -> Ptr () -> IO CInt
- type StructureForeachFunc = Word32 -> GValue -> IO Bool
- type StructureForeachFunc_WithClosures = Word32 -> GValue -> Ptr () -> IO Bool
- drop_closures_StructureForeachFunc :: StructureForeachFunc -> StructureForeachFunc_WithClosures
- dynamic_StructureForeachFunc :: (HasCallStack, MonadIO m) => FunPtr C_StructureForeachFunc -> Word32 -> GValue -> Ptr () -> m Bool
- genClosure_StructureForeachFunc :: MonadIO m => StructureForeachFunc -> m (GClosure C_StructureForeachFunc)
- mk_StructureForeachFunc :: C_StructureForeachFunc -> IO (FunPtr C_StructureForeachFunc)
- noStructureForeachFunc :: Maybe StructureForeachFunc
- noStructureForeachFunc_WithClosures :: Maybe StructureForeachFunc_WithClosures
- wrap_StructureForeachFunc :: Maybe (Ptr (FunPtr C_StructureForeachFunc)) -> StructureForeachFunc_WithClosures -> C_StructureForeachFunc
- type C_StructureMapFunc = Word32 -> Ptr GValue -> Ptr () -> IO CInt
- type StructureMapFunc = Word32 -> GValue -> IO Bool
- type StructureMapFunc_WithClosures = Word32 -> GValue -> Ptr () -> IO Bool
- drop_closures_StructureMapFunc :: StructureMapFunc -> StructureMapFunc_WithClosures
- dynamic_StructureMapFunc :: (HasCallStack, MonadIO m) => FunPtr C_StructureMapFunc -> Word32 -> GValue -> Ptr () -> m Bool
- genClosure_StructureMapFunc :: MonadIO m => StructureMapFunc -> m (GClosure C_StructureMapFunc)
- mk_StructureMapFunc :: C_StructureMapFunc -> IO (FunPtr C_StructureMapFunc)
- noStructureMapFunc :: Maybe StructureMapFunc
- noStructureMapFunc_WithClosures :: Maybe StructureMapFunc_WithClosures
- wrap_StructureMapFunc :: Maybe (Ptr (FunPtr C_StructureMapFunc)) -> StructureMapFunc_WithClosures -> C_StructureMapFunc
- type C_TagForeachFunc = Ptr TagList -> CString -> Ptr () -> IO ()
- type TagForeachFunc = TagList -> Text -> IO ()
- type TagForeachFunc_WithClosures = TagList -> Text -> Ptr () -> IO ()
- drop_closures_TagForeachFunc :: TagForeachFunc -> TagForeachFunc_WithClosures
- dynamic_TagForeachFunc :: (HasCallStack, MonadIO m) => FunPtr C_TagForeachFunc -> TagList -> Text -> Ptr () -> m ()
- genClosure_TagForeachFunc :: MonadIO m => TagForeachFunc -> m (GClosure C_TagForeachFunc)
- mk_TagForeachFunc :: C_TagForeachFunc -> IO (FunPtr C_TagForeachFunc)
- noTagForeachFunc :: Maybe TagForeachFunc
- noTagForeachFunc_WithClosures :: Maybe TagForeachFunc_WithClosures
- wrap_TagForeachFunc :: Maybe (Ptr (FunPtr C_TagForeachFunc)) -> TagForeachFunc_WithClosures -> C_TagForeachFunc
- type C_TagMergeFunc = Ptr GValue -> Ptr GValue -> IO ()
- type TagMergeFunc = GValue -> GValue -> IO ()
- dynamic_TagMergeFunc :: (HasCallStack, MonadIO m) => FunPtr C_TagMergeFunc -> GValue -> GValue -> m ()
- genClosure_TagMergeFunc :: MonadIO m => TagMergeFunc -> m (GClosure C_TagMergeFunc)
- mk_TagMergeFunc :: C_TagMergeFunc -> IO (FunPtr C_TagMergeFunc)
- noTagMergeFunc :: Maybe TagMergeFunc
- wrap_TagMergeFunc :: Maybe (Ptr (FunPtr C_TagMergeFunc)) -> TagMergeFunc -> C_TagMergeFunc
- type C_TaskFunction = Ptr () -> IO ()
- type TaskFunction = IO ()
- type TaskFunction_WithClosures = Ptr () -> IO ()
- drop_closures_TaskFunction :: TaskFunction -> TaskFunction_WithClosures
- dynamic_TaskFunction :: (HasCallStack, MonadIO m) => FunPtr C_TaskFunction -> Ptr () -> m ()
- genClosure_TaskFunction :: MonadIO m => TaskFunction -> m (GClosure C_TaskFunction)
- mk_TaskFunction :: C_TaskFunction -> IO (FunPtr C_TaskFunction)
- noTaskFunction :: Maybe TaskFunction
- noTaskFunction_WithClosures :: Maybe TaskFunction_WithClosures
- wrap_TaskFunction :: Maybe (Ptr (FunPtr C_TaskFunction)) -> TaskFunction_WithClosures -> C_TaskFunction
- type C_TaskPoolFunction = Ptr () -> IO ()
- type TaskPoolFunction = IO ()
- type TaskPoolFunction_WithClosures = Ptr () -> IO ()
- drop_closures_TaskPoolFunction :: TaskPoolFunction -> TaskPoolFunction_WithClosures
- dynamic_TaskPoolFunction :: (HasCallStack, MonadIO m) => FunPtr C_TaskPoolFunction -> Ptr () -> m ()
- genClosure_TaskPoolFunction :: MonadIO m => TaskPoolFunction -> m (GClosure C_TaskPoolFunction)
- mk_TaskPoolFunction :: C_TaskPoolFunction -> IO (FunPtr C_TaskPoolFunction)
- noTaskPoolFunction :: Maybe TaskPoolFunction
- noTaskPoolFunction_WithClosures :: Maybe TaskPoolFunction_WithClosures
- wrap_TaskPoolFunction :: Maybe (Ptr (FunPtr C_TaskPoolFunction)) -> TaskPoolFunction_WithClosures -> C_TaskPoolFunction
- type C_TaskThreadFunc = Ptr Task -> Ptr Thread -> Ptr () -> IO ()
- type TaskThreadFunc = Task -> Thread -> IO ()
- type TaskThreadFunc_WithClosures = Task -> Thread -> Ptr () -> IO ()
- drop_closures_TaskThreadFunc :: TaskThreadFunc -> TaskThreadFunc_WithClosures
- dynamic_TaskThreadFunc :: (HasCallStack, MonadIO m, IsTask a) => FunPtr C_TaskThreadFunc -> a -> Thread -> Ptr () -> m ()
- genClosure_TaskThreadFunc :: MonadIO m => TaskThreadFunc -> m (GClosure C_TaskThreadFunc)
- mk_TaskThreadFunc :: C_TaskThreadFunc -> IO (FunPtr C_TaskThreadFunc)
- noTaskThreadFunc :: Maybe TaskThreadFunc
- noTaskThreadFunc_WithClosures :: Maybe TaskThreadFunc_WithClosures
- wrap_TaskThreadFunc :: Maybe (Ptr (FunPtr C_TaskThreadFunc)) -> TaskThreadFunc_WithClosures -> C_TaskThreadFunc
- type C_TypeFindFunction = Ptr TypeFind -> Ptr () -> IO ()
- type TypeFindFunction = TypeFind -> IO ()
- type TypeFindFunction_WithClosures = TypeFind -> Ptr () -> IO ()
- drop_closures_TypeFindFunction :: TypeFindFunction -> TypeFindFunction_WithClosures
- dynamic_TypeFindFunction :: (HasCallStack, MonadIO m) => FunPtr C_TypeFindFunction -> TypeFind -> Ptr () -> m ()
- genClosure_TypeFindFunction :: MonadIO m => TypeFindFunction -> m (GClosure C_TypeFindFunction)
- mk_TypeFindFunction :: C_TypeFindFunction -> IO (FunPtr C_TypeFindFunction)
- noTypeFindFunction :: Maybe TypeFindFunction
- noTypeFindFunction_WithClosures :: Maybe TypeFindFunction_WithClosures
- wrap_TypeFindFunction :: Maybe (Ptr (FunPtr C_TypeFindFunction)) -> TypeFindFunction_WithClosures -> C_TypeFindFunction
- type C_TypeFindGetLengthFieldCallback = Ptr () -> IO Word64
- type TypeFindGetLengthFieldCallback = Ptr () -> IO Word64
- dynamic_TypeFindGetLengthFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_TypeFindGetLengthFieldCallback -> Ptr () -> m Word64
- genClosure_TypeFindGetLengthFieldCallback :: MonadIO m => TypeFindGetLengthFieldCallback -> m (GClosure C_TypeFindGetLengthFieldCallback)
- mk_TypeFindGetLengthFieldCallback :: C_TypeFindGetLengthFieldCallback -> IO (FunPtr C_TypeFindGetLengthFieldCallback)
- noTypeFindGetLengthFieldCallback :: Maybe TypeFindGetLengthFieldCallback
- wrap_TypeFindGetLengthFieldCallback :: Maybe (Ptr (FunPtr C_TypeFindGetLengthFieldCallback)) -> TypeFindGetLengthFieldCallback -> C_TypeFindGetLengthFieldCallback
- type C_TypeFindPeekFieldCallback = Ptr () -> Int64 -> Word32 -> IO Word8
- type TypeFindPeekFieldCallback = Ptr () -> Int64 -> Word32 -> IO Word8
- dynamic_TypeFindPeekFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_TypeFindPeekFieldCallback -> Ptr () -> Int64 -> Word32 -> m Word8
- genClosure_TypeFindPeekFieldCallback :: MonadIO m => TypeFindPeekFieldCallback -> m (GClosure C_TypeFindPeekFieldCallback)
- mk_TypeFindPeekFieldCallback :: C_TypeFindPeekFieldCallback -> IO (FunPtr C_TypeFindPeekFieldCallback)
- noTypeFindPeekFieldCallback :: Maybe TypeFindPeekFieldCallback
- wrap_TypeFindPeekFieldCallback :: Maybe (Ptr (FunPtr C_TypeFindPeekFieldCallback)) -> TypeFindPeekFieldCallback -> C_TypeFindPeekFieldCallback
- type C_TypeFindSuggestFieldCallback = Ptr () -> Word32 -> Ptr Caps -> IO ()
- type TypeFindSuggestFieldCallback = Ptr () -> Word32 -> Caps -> IO ()
- dynamic_TypeFindSuggestFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_TypeFindSuggestFieldCallback -> Ptr () -> Word32 -> Caps -> m ()
- genClosure_TypeFindSuggestFieldCallback :: MonadIO m => TypeFindSuggestFieldCallback -> m (GClosure C_TypeFindSuggestFieldCallback)
- mk_TypeFindSuggestFieldCallback :: C_TypeFindSuggestFieldCallback -> IO (FunPtr C_TypeFindSuggestFieldCallback)
- noTypeFindSuggestFieldCallback :: Maybe TypeFindSuggestFieldCallback
- wrap_TypeFindSuggestFieldCallback :: Maybe (Ptr (FunPtr C_TypeFindSuggestFieldCallback)) -> TypeFindSuggestFieldCallback -> C_TypeFindSuggestFieldCallback
- type C_ValueCompareFunc = Ptr GValue -> Ptr GValue -> IO Int32
- type ValueCompareFunc = GValue -> GValue -> IO Int32
- dynamic_ValueCompareFunc :: (HasCallStack, MonadIO m) => FunPtr C_ValueCompareFunc -> GValue -> GValue -> m Int32
- genClosure_ValueCompareFunc :: MonadIO m => ValueCompareFunc -> m (GClosure C_ValueCompareFunc)
- mk_ValueCompareFunc :: C_ValueCompareFunc -> IO (FunPtr C_ValueCompareFunc)
- noValueCompareFunc :: Maybe ValueCompareFunc
- wrap_ValueCompareFunc :: Maybe (Ptr (FunPtr C_ValueCompareFunc)) -> ValueCompareFunc -> C_ValueCompareFunc
- type C_ValueDeserializeFunc = Ptr GValue -> CString -> IO CInt
- type ValueDeserializeFunc = GValue -> Text -> IO Bool
- dynamic_ValueDeserializeFunc :: (HasCallStack, MonadIO m) => FunPtr C_ValueDeserializeFunc -> GValue -> Text -> m Bool
- genClosure_ValueDeserializeFunc :: MonadIO m => ValueDeserializeFunc -> m (GClosure C_ValueDeserializeFunc)
- mk_ValueDeserializeFunc :: C_ValueDeserializeFunc -> IO (FunPtr C_ValueDeserializeFunc)
- noValueDeserializeFunc :: Maybe ValueDeserializeFunc
- wrap_ValueDeserializeFunc :: Maybe (Ptr (FunPtr C_ValueDeserializeFunc)) -> ValueDeserializeFunc -> C_ValueDeserializeFunc
- type C_ValueSerializeFunc = Ptr GValue -> IO CString
- type ValueSerializeFunc = GValue -> IO Text
- dynamic_ValueSerializeFunc :: (HasCallStack, MonadIO m) => FunPtr C_ValueSerializeFunc -> GValue -> m Text
- genClosure_ValueSerializeFunc :: MonadIO m => ValueSerializeFunc -> m (GClosure C_ValueSerializeFunc)
- mk_ValueSerializeFunc :: C_ValueSerializeFunc -> IO (FunPtr C_ValueSerializeFunc)
- noValueSerializeFunc :: Maybe ValueSerializeFunc
- wrap_ValueSerializeFunc :: Maybe (Ptr (FunPtr C_ValueSerializeFunc)) -> ValueSerializeFunc -> C_ValueSerializeFunc
Signals
BufferForeachMetaFunc
type BufferForeachMetaFunc Source #
A function that will be called from bufferForeachMeta
. The meta
field will point to a the reference of the meta.
buffer
should not be modified from this callback.
When this function returns True
, the next meta will be
returned. When False
is returned, bufferForeachMeta
will return.
When meta
is set to Nothing
, the item will be removed from the buffer.
type BufferForeachMetaFunc_WithClosures Source #
= Buffer |
|
-> Ptr () |
|
-> IO (Bool, Maybe Meta) | Returns: |
A function that will be called from bufferForeachMeta
. The meta
field will point to a the reference of the meta.
buffer
should not be modified from this callback.
When this function returns True
, the next meta will be
returned. When False
is returned, bufferForeachMeta
will return.
When meta
is set to Nothing
, the item will be removed from the buffer.
type C_BufferForeachMetaFunc = Ptr Buffer -> Ptr (Ptr Meta) -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BufferForeachMetaFunc :: BufferForeachMetaFunc -> BufferForeachMetaFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BufferForeachMetaFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_BufferForeachMetaFunc | |
-> Buffer |
|
-> Ptr () |
|
-> m (Bool, Maybe Meta) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BufferForeachMetaFunc :: MonadIO m => BufferForeachMetaFunc -> m (GClosure C_BufferForeachMetaFunc) Source #
Wrap the callback into a GClosure
.
mk_BufferForeachMetaFunc :: C_BufferForeachMetaFunc -> IO (FunPtr C_BufferForeachMetaFunc) Source #
Generate a function pointer callable from C code, from a C_BufferForeachMetaFunc
.
noBufferForeachMetaFunc :: Maybe BufferForeachMetaFunc Source #
A convenience synonym for
.Nothing
:: Maybe
BufferForeachMetaFunc
noBufferForeachMetaFunc_WithClosures :: Maybe BufferForeachMetaFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BufferForeachMetaFunc_WithClosures
wrap_BufferForeachMetaFunc :: Maybe (Ptr (FunPtr C_BufferForeachMetaFunc)) -> BufferForeachMetaFunc_WithClosures -> C_BufferForeachMetaFunc Source #
Wrap a BufferForeachMetaFunc
into a C_BufferForeachMetaFunc
.
BufferListFunc
type BufferListFunc Source #
= Word32 |
|
-> IO (Bool, Maybe Buffer) | Returns: |
A function that will be called from bufferListForeach
. The buffer
field will point to a the reference of the buffer at idx
.
When this function returns True
, the next buffer will be
returned. When False
is returned, bufferListForeach
will return.
When buffer
is set to Nothing
, the item will be removed from the bufferlist.
When buffer
has been made writable, the new buffer reference can be assigned
to buffer
. This function is responsible for unreffing the old buffer when
removing or modifying.
type BufferListFunc_WithClosures Source #
= Word32 |
|
-> Ptr () |
|
-> IO (Bool, Maybe Buffer) | Returns: |
A function that will be called from bufferListForeach
. The buffer
field will point to a the reference of the buffer at idx
.
When this function returns True
, the next buffer will be
returned. When False
is returned, bufferListForeach
will return.
When buffer
is set to Nothing
, the item will be removed from the bufferlist.
When buffer
has been made writable, the new buffer reference can be assigned
to buffer
. This function is responsible for unreffing the old buffer when
removing or modifying.
type C_BufferListFunc = Ptr (Ptr Buffer) -> Word32 -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BufferListFunc :: BufferListFunc -> BufferListFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BufferListFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_BufferListFunc | |
-> Word32 |
|
-> Ptr () |
|
-> m (Bool, Maybe Buffer) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BufferListFunc :: MonadIO m => BufferListFunc -> m (GClosure C_BufferListFunc) Source #
Wrap the callback into a GClosure
.
mk_BufferListFunc :: C_BufferListFunc -> IO (FunPtr C_BufferListFunc) Source #
Generate a function pointer callable from C code, from a C_BufferListFunc
.
noBufferListFunc :: Maybe BufferListFunc Source #
A convenience synonym for
.Nothing
:: Maybe
BufferListFunc
noBufferListFunc_WithClosures :: Maybe BufferListFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BufferListFunc_WithClosures
wrap_BufferListFunc :: Maybe (Ptr (FunPtr C_BufferListFunc)) -> BufferListFunc_WithClosures -> C_BufferListFunc Source #
Wrap a BufferListFunc
into a C_BufferListFunc
.
BusFunc
= Bus |
|
-> Message |
|
-> IO Bool | Returns: |
Specifies the type of function passed to gst_bus_add_watch()
or
busAddWatch
, which is called from the mainloop when a message
is available on the bus.
The message passed to the function will be unreffed after execution of this function so it should not be freed in the function.
Note that this function is used as a GSourceFunc which means that returning
False
will remove the GSource from the mainloop.
type BusFunc_WithClosures Source #
= Bus |
|
-> Message |
|
-> Ptr () |
|
-> IO Bool | Returns: |
Specifies the type of function passed to gst_bus_add_watch()
or
busAddWatch
, which is called from the mainloop when a message
is available on the bus.
The message passed to the function will be unreffed after execution of this function so it should not be freed in the function.
Note that this function is used as a GSourceFunc which means that returning
False
will remove the GSource from the mainloop.
type C_BusFunc = Ptr Bus -> Ptr Message -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BusFunc :: BusFunc -> BusFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m, IsBus a) | |
=> FunPtr C_BusFunc | |
-> a |
|
-> Message |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BusFunc :: MonadIO m => BusFunc -> m (GClosure C_BusFunc) Source #
Wrap the callback into a GClosure
.
mk_BusFunc :: C_BusFunc -> IO (FunPtr C_BusFunc) Source #
Generate a function pointer callable from C code, from a C_BusFunc
.
noBusFunc_WithClosures :: Maybe BusFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BusFunc_WithClosures
wrap_BusFunc :: Maybe (Ptr (FunPtr C_BusFunc)) -> BusFunc_WithClosures -> C_BusFunc Source #
BusSyncHandler
type BusSyncHandler Source #
= Bus |
|
-> Message |
|
-> IO BusSyncReply | Returns: |
Handler will be invoked synchronously, when a new message has been injected into the bus. This function is mostly used internally. Only one sync handler can be attached to a given bus.
If the handler returns GST_BUS_DROP, it should unref the message, else the message should not be unreffed by the sync handler.
type BusSyncHandler_WithClosures Source #
= Bus |
|
-> Message |
|
-> Ptr () |
|
-> IO BusSyncReply | Returns: |
Handler will be invoked synchronously, when a new message has been injected into the bus. This function is mostly used internally. Only one sync handler can be attached to a given bus.
If the handler returns GST_BUS_DROP, it should unref the message, else the message should not be unreffed by the sync handler.
type C_BusSyncHandler = Ptr Bus -> Ptr Message -> Ptr () -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BusSyncHandler :: BusSyncHandler -> BusSyncHandler_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BusSyncHandler Source #
:: (HasCallStack, MonadIO m, IsBus a) | |
=> FunPtr C_BusSyncHandler | |
-> a |
|
-> Message |
|
-> Ptr () |
|
-> m BusSyncReply | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BusSyncHandler :: MonadIO m => BusSyncHandler -> m (GClosure C_BusSyncHandler) Source #
Wrap the callback into a GClosure
.
mk_BusSyncHandler :: C_BusSyncHandler -> IO (FunPtr C_BusSyncHandler) Source #
Generate a function pointer callable from C code, from a C_BusSyncHandler
.
noBusSyncHandler :: Maybe BusSyncHandler Source #
A convenience synonym for
.Nothing
:: Maybe
BusSyncHandler
noBusSyncHandler_WithClosures :: Maybe BusSyncHandler_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BusSyncHandler_WithClosures
wrap_BusSyncHandler :: Maybe (Ptr (FunPtr C_BusSyncHandler)) -> BusSyncHandler_WithClosures -> C_BusSyncHandler Source #
Wrap a BusSyncHandler
into a C_BusSyncHandler
.
CapsFilterMapFunc
type C_CapsFilterMapFunc = Ptr CapsFeatures -> Ptr Structure -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type CapsFilterMapFunc Source #
= CapsFeatures |
|
-> Structure |
|
-> IO Bool | Returns: |
A function that will be called in capsFilterAndMapInPlace
.
The function may modify features
and structure
, and both will be
removed from the caps if False
is returned.
type CapsFilterMapFunc_WithClosures Source #
= CapsFeatures |
|
-> Structure |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function that will be called in capsFilterAndMapInPlace
.
The function may modify features
and structure
, and both will be
removed from the caps if False
is returned.
drop_closures_CapsFilterMapFunc :: CapsFilterMapFunc -> CapsFilterMapFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_CapsFilterMapFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_CapsFilterMapFunc | |
-> CapsFeatures |
|
-> Structure |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CapsFilterMapFunc :: MonadIO m => CapsFilterMapFunc -> m (GClosure C_CapsFilterMapFunc) Source #
Wrap the callback into a GClosure
.
mk_CapsFilterMapFunc :: C_CapsFilterMapFunc -> IO (FunPtr C_CapsFilterMapFunc) Source #
Generate a function pointer callable from C code, from a C_CapsFilterMapFunc
.
noCapsFilterMapFunc :: Maybe CapsFilterMapFunc Source #
A convenience synonym for
.Nothing
:: Maybe
CapsFilterMapFunc
noCapsFilterMapFunc_WithClosures :: Maybe CapsFilterMapFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
CapsFilterMapFunc_WithClosures
wrap_CapsFilterMapFunc :: Maybe (Ptr (FunPtr C_CapsFilterMapFunc)) -> CapsFilterMapFunc_WithClosures -> C_CapsFilterMapFunc Source #
Wrap a CapsFilterMapFunc
into a C_CapsFilterMapFunc
.
CapsForeachFunc
type C_CapsForeachFunc = Ptr CapsFeatures -> Ptr Structure -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type CapsForeachFunc Source #
= CapsFeatures |
|
-> Structure |
|
-> IO Bool | Returns: |
A function that will be called in capsForeach
. The function may
not modify features
or structure
.
Since: 1.6
type CapsForeachFunc_WithClosures Source #
= CapsFeatures |
|
-> Structure |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function that will be called in capsForeach
. The function may
not modify features
or structure
.
Since: 1.6
drop_closures_CapsForeachFunc :: CapsForeachFunc -> CapsForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_CapsForeachFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_CapsForeachFunc | |
-> CapsFeatures |
|
-> Structure |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CapsForeachFunc :: MonadIO m => CapsForeachFunc -> m (GClosure C_CapsForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_CapsForeachFunc :: C_CapsForeachFunc -> IO (FunPtr C_CapsForeachFunc) Source #
Generate a function pointer callable from C code, from a C_CapsForeachFunc
.
noCapsForeachFunc :: Maybe CapsForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
CapsForeachFunc
noCapsForeachFunc_WithClosures :: Maybe CapsForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
CapsForeachFunc_WithClosures
wrap_CapsForeachFunc :: Maybe (Ptr (FunPtr C_CapsForeachFunc)) -> CapsForeachFunc_WithClosures -> C_CapsForeachFunc Source #
Wrap a CapsForeachFunc
into a C_CapsForeachFunc
.
CapsMapFunc
type C_CapsMapFunc = Ptr CapsFeatures -> Ptr Structure -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type CapsMapFunc Source #
= CapsFeatures |
|
-> Structure |
|
-> IO Bool | Returns: |
A function that will be called in capsMapInPlace
. The function
may modify features
and structure
.
type CapsMapFunc_WithClosures Source #
= CapsFeatures |
|
-> Structure |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function that will be called in capsMapInPlace
. The function
may modify features
and structure
.
drop_closures_CapsMapFunc :: CapsMapFunc -> CapsMapFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_CapsMapFunc | |
-> CapsFeatures |
|
-> Structure |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CapsMapFunc :: MonadIO m => CapsMapFunc -> m (GClosure C_CapsMapFunc) Source #
Wrap the callback into a GClosure
.
mk_CapsMapFunc :: C_CapsMapFunc -> IO (FunPtr C_CapsMapFunc) Source #
Generate a function pointer callable from C code, from a C_CapsMapFunc
.
noCapsMapFunc :: Maybe CapsMapFunc Source #
A convenience synonym for
.Nothing
:: Maybe
CapsMapFunc
noCapsMapFunc_WithClosures :: Maybe CapsMapFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
CapsMapFunc_WithClosures
wrap_CapsMapFunc :: Maybe (Ptr (FunPtr C_CapsMapFunc)) -> CapsMapFunc_WithClosures -> C_CapsMapFunc Source #
Wrap a CapsMapFunc
into a C_CapsMapFunc
.
ClockCallback
type C_ClockCallback = Ptr Clock -> Word64 -> Ptr () -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ClockCallback Source #
= Clock |
|
-> Word64 |
|
-> Ptr () |
|
-> IO Bool |
The function prototype of the callback.
type ClockCallback_WithClosures Source #
= Clock |
|
-> Word64 |
|
-> Ptr () |
|
-> Ptr () |
|
-> IO Bool |
The function prototype of the callback.
drop_closures_ClockCallback :: ClockCallback -> ClockCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ClockCallback Source #
:: (HasCallStack, MonadIO m, IsClock a) | |
=> FunPtr C_ClockCallback | |
-> a |
|
-> Word64 |
|
-> Ptr () |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ClockCallback :: MonadIO m => ClockCallback -> m (GClosure C_ClockCallback) Source #
Wrap the callback into a GClosure
.
mk_ClockCallback :: C_ClockCallback -> IO (FunPtr C_ClockCallback) Source #
Generate a function pointer callable from C code, from a C_ClockCallback
.
noClockCallback :: Maybe ClockCallback Source #
A convenience synonym for
.Nothing
:: Maybe
ClockCallback
noClockCallback_WithClosures :: Maybe ClockCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ClockCallback_WithClosures
wrap_ClockCallback :: Maybe (Ptr (FunPtr C_ClockCallback)) -> ClockCallback_WithClosures -> C_ClockCallback Source #
Wrap a ClockCallback
into a C_ClockCallback
.
ControlBindingConvert
type C_ControlBindingConvert = Ptr ControlBinding -> CDouble -> Ptr GValue -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ControlBindingConvert = ControlBinding -> Double -> GValue -> IO () Source #
No description available in the introspection data.
dynamic_ControlBindingConvert :: (HasCallStack, MonadIO m, IsControlBinding a) => FunPtr C_ControlBindingConvert -> a -> Double -> GValue -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ControlBindingConvert :: MonadIO m => ControlBindingConvert -> m (GClosure C_ControlBindingConvert) Source #
Wrap the callback into a GClosure
.
mk_ControlBindingConvert :: C_ControlBindingConvert -> IO (FunPtr C_ControlBindingConvert) Source #
Generate a function pointer callable from C code, from a C_ControlBindingConvert
.
noControlBindingConvert :: Maybe ControlBindingConvert Source #
A convenience synonym for
.Nothing
:: Maybe
ControlBindingConvert
wrap_ControlBindingConvert :: Maybe (Ptr (FunPtr C_ControlBindingConvert)) -> ControlBindingConvert -> C_ControlBindingConvert Source #
Wrap a ControlBindingConvert
into a C_ControlBindingConvert
.
ControlSourceGetValue
type C_ControlSourceGetValue = Ptr ControlSource -> Word64 -> CDouble -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ControlSourceGetValue Source #
= ControlSource |
|
-> Word64 |
|
-> Double |
|
-> IO Bool | Returns: |
Function for returning a value for a given timestamp.
dynamic_ControlSourceGetValue Source #
:: (HasCallStack, MonadIO m, IsControlSource a) | |
=> FunPtr C_ControlSourceGetValue | |
-> a |
|
-> Word64 |
|
-> Double |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ControlSourceGetValue :: MonadIO m => ControlSourceGetValue -> m (GClosure C_ControlSourceGetValue) Source #
Wrap the callback into a GClosure
.
mk_ControlSourceGetValue :: C_ControlSourceGetValue -> IO (FunPtr C_ControlSourceGetValue) Source #
Generate a function pointer callable from C code, from a C_ControlSourceGetValue
.
noControlSourceGetValue :: Maybe ControlSourceGetValue Source #
A convenience synonym for
.Nothing
:: Maybe
ControlSourceGetValue
wrap_ControlSourceGetValue :: Maybe (Ptr (FunPtr C_ControlSourceGetValue)) -> ControlSourceGetValue -> C_ControlSourceGetValue Source #
Wrap a ControlSourceGetValue
into a C_ControlSourceGetValue
.
ControlSourceGetValueArray
type C_ControlSourceGetValueArray = Ptr ControlSource -> Word64 -> Word64 -> Word32 -> CDouble -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ControlSourceGetValueArray Source #
= ControlSource |
|
-> Word64 |
|
-> Word64 |
|
-> Word32 |
|
-> Double |
|
-> IO Bool | Returns: |
Function for returning an array of values for starting at a given timestamp.
dynamic_ControlSourceGetValueArray Source #
:: (HasCallStack, MonadIO m, IsControlSource a) | |
=> FunPtr C_ControlSourceGetValueArray | |
-> a |
|
-> Word64 |
|
-> Word64 |
|
-> Word32 |
|
-> Double |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ControlSourceGetValueArray :: MonadIO m => ControlSourceGetValueArray -> m (GClosure C_ControlSourceGetValueArray) Source #
Wrap the callback into a GClosure
.
mk_ControlSourceGetValueArray :: C_ControlSourceGetValueArray -> IO (FunPtr C_ControlSourceGetValueArray) Source #
Generate a function pointer callable from C code, from a C_ControlSourceGetValueArray
.
noControlSourceGetValueArray :: Maybe ControlSourceGetValueArray Source #
A convenience synonym for
.Nothing
:: Maybe
ControlSourceGetValueArray
wrap_ControlSourceGetValueArray :: Maybe (Ptr (FunPtr C_ControlSourceGetValueArray)) -> ControlSourceGetValueArray -> C_ControlSourceGetValueArray Source #
Wrap a ControlSourceGetValueArray
into a C_ControlSourceGetValueArray
.
DebugFuncPtr
type C_DebugFuncPtr = IO () Source #
Type for the callback on the (unwrapped) C side.
type DebugFuncPtr = IO () Source #
No description available in the introspection data.
dynamic_DebugFuncPtr :: (HasCallStack, MonadIO m) => FunPtr C_DebugFuncPtr -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DebugFuncPtr :: MonadIO m => DebugFuncPtr -> m (GClosure C_DebugFuncPtr) Source #
Wrap the callback into a GClosure
.
mk_DebugFuncPtr :: C_DebugFuncPtr -> IO (FunPtr C_DebugFuncPtr) Source #
Generate a function pointer callable from C code, from a C_DebugFuncPtr
.
noDebugFuncPtr :: Maybe DebugFuncPtr Source #
A convenience synonym for
.Nothing
:: Maybe
DebugFuncPtr
wrap_DebugFuncPtr :: Maybe (Ptr (FunPtr C_DebugFuncPtr)) -> DebugFuncPtr -> C_DebugFuncPtr Source #
Wrap a DebugFuncPtr
into a C_DebugFuncPtr
.
ElementCallAsyncFunc
type C_ElementCallAsyncFunc = Ptr Element -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type ElementCallAsyncFunc = Element -> IO () Source #
No description available in the introspection data.
type ElementCallAsyncFunc_WithClosures = Element -> Ptr () -> IO () Source #
No description available in the introspection data.
drop_closures_ElementCallAsyncFunc :: ElementCallAsyncFunc -> ElementCallAsyncFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ElementCallAsyncFunc :: (HasCallStack, MonadIO m, IsElement a) => FunPtr C_ElementCallAsyncFunc -> a -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ElementCallAsyncFunc :: MonadIO m => ElementCallAsyncFunc -> m (GClosure C_ElementCallAsyncFunc) Source #
Wrap the callback into a GClosure
.
mk_ElementCallAsyncFunc :: C_ElementCallAsyncFunc -> IO (FunPtr C_ElementCallAsyncFunc) Source #
Generate a function pointer callable from C code, from a C_ElementCallAsyncFunc
.
noElementCallAsyncFunc :: Maybe ElementCallAsyncFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ElementCallAsyncFunc
noElementCallAsyncFunc_WithClosures :: Maybe ElementCallAsyncFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ElementCallAsyncFunc_WithClosures
wrap_ElementCallAsyncFunc :: Maybe (Ptr (FunPtr C_ElementCallAsyncFunc)) -> ElementCallAsyncFunc_WithClosures -> C_ElementCallAsyncFunc Source #
Wrap a ElementCallAsyncFunc
into a C_ElementCallAsyncFunc
.
ElementForeachPadFunc
type C_ElementForeachPadFunc = Ptr Element -> Ptr Pad -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ElementForeachPadFunc Source #
Function called for each pad when using elementForeachSinkPad
,
elementForeachSrcPad
, or elementForeachPad
.
Since: 1.14
type ElementForeachPadFunc_WithClosures Source #
= Element |
|
-> Pad |
|
-> Ptr () |
|
-> IO Bool |
Function called for each pad when using elementForeachSinkPad
,
elementForeachSrcPad
, or elementForeachPad
.
Since: 1.14
drop_closures_ElementForeachPadFunc :: ElementForeachPadFunc -> ElementForeachPadFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ElementForeachPadFunc Source #
:: (HasCallStack, MonadIO m, IsElement a, IsPad b) | |
=> FunPtr C_ElementForeachPadFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ElementForeachPadFunc :: MonadIO m => ElementForeachPadFunc -> m (GClosure C_ElementForeachPadFunc) Source #
Wrap the callback into a GClosure
.
mk_ElementForeachPadFunc :: C_ElementForeachPadFunc -> IO (FunPtr C_ElementForeachPadFunc) Source #
Generate a function pointer callable from C code, from a C_ElementForeachPadFunc
.
noElementForeachPadFunc :: Maybe ElementForeachPadFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ElementForeachPadFunc
noElementForeachPadFunc_WithClosures :: Maybe ElementForeachPadFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ElementForeachPadFunc_WithClosures
wrap_ElementForeachPadFunc :: Maybe (Ptr (FunPtr C_ElementForeachPadFunc)) -> ElementForeachPadFunc_WithClosures -> C_ElementForeachPadFunc Source #
Wrap a ElementForeachPadFunc
into a C_ElementForeachPadFunc
.
IteratorCopyFunction
type C_IteratorCopyFunction = Ptr Iterator -> Ptr Iterator -> IO () Source #
Type for the callback on the (unwrapped) C side.
type IteratorCopyFunction Source #
This function will be called when creating a copy of it
and should
create a copy of all custom iterator fields or increase their
reference counts.
dynamic_IteratorCopyFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_IteratorCopyFunction | |
-> Iterator |
|
-> Iterator |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IteratorCopyFunction :: MonadIO m => IteratorCopyFunction -> m (GClosure C_IteratorCopyFunction) Source #
Wrap the callback into a GClosure
.
mk_IteratorCopyFunction :: C_IteratorCopyFunction -> IO (FunPtr C_IteratorCopyFunction) Source #
Generate a function pointer callable from C code, from a C_IteratorCopyFunction
.
noIteratorCopyFunction :: Maybe IteratorCopyFunction Source #
A convenience synonym for
.Nothing
:: Maybe
IteratorCopyFunction
wrap_IteratorCopyFunction :: Maybe (Ptr (FunPtr C_IteratorCopyFunction)) -> IteratorCopyFunction -> C_IteratorCopyFunction Source #
Wrap a IteratorCopyFunction
into a C_IteratorCopyFunction
.
IteratorFoldFunction
type C_IteratorFoldFunction = Ptr GValue -> Ptr GValue -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type IteratorFoldFunction Source #
= GValue |
|
-> GValue |
|
-> IO Bool | Returns: |
A function to be passed to iteratorFold
.
type IteratorFoldFunction_WithClosures Source #
= GValue |
|
-> GValue |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function to be passed to iteratorFold
.
drop_closures_IteratorFoldFunction :: IteratorFoldFunction -> IteratorFoldFunction_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_IteratorFoldFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_IteratorFoldFunction | |
-> GValue |
|
-> GValue |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IteratorFoldFunction :: MonadIO m => IteratorFoldFunction -> m (GClosure C_IteratorFoldFunction) Source #
Wrap the callback into a GClosure
.
mk_IteratorFoldFunction :: C_IteratorFoldFunction -> IO (FunPtr C_IteratorFoldFunction) Source #
Generate a function pointer callable from C code, from a C_IteratorFoldFunction
.
noIteratorFoldFunction :: Maybe IteratorFoldFunction Source #
A convenience synonym for
.Nothing
:: Maybe
IteratorFoldFunction
noIteratorFoldFunction_WithClosures :: Maybe IteratorFoldFunction_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
IteratorFoldFunction_WithClosures
wrap_IteratorFoldFunction :: Maybe (Ptr (FunPtr C_IteratorFoldFunction)) -> IteratorFoldFunction_WithClosures -> C_IteratorFoldFunction Source #
Wrap a IteratorFoldFunction
into a C_IteratorFoldFunction
.
IteratorForeachFunction
type C_IteratorForeachFunction = Ptr GValue -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type IteratorForeachFunction Source #
A function that is called by iteratorForeach
for every element.
type IteratorForeachFunction_WithClosures Source #
A function that is called by iteratorForeach
for every element.
drop_closures_IteratorForeachFunction :: IteratorForeachFunction -> IteratorForeachFunction_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_IteratorForeachFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_IteratorForeachFunction | |
-> GValue |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IteratorForeachFunction :: MonadIO m => IteratorForeachFunction -> m (GClosure C_IteratorForeachFunction) Source #
Wrap the callback into a GClosure
.
mk_IteratorForeachFunction :: C_IteratorForeachFunction -> IO (FunPtr C_IteratorForeachFunction) Source #
Generate a function pointer callable from C code, from a C_IteratorForeachFunction
.
noIteratorForeachFunction :: Maybe IteratorForeachFunction Source #
A convenience synonym for
.Nothing
:: Maybe
IteratorForeachFunction
noIteratorForeachFunction_WithClosures :: Maybe IteratorForeachFunction_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
IteratorForeachFunction_WithClosures
wrap_IteratorForeachFunction :: Maybe (Ptr (FunPtr C_IteratorForeachFunction)) -> IteratorForeachFunction_WithClosures -> C_IteratorForeachFunction Source #
Wrap a IteratorForeachFunction
into a C_IteratorForeachFunction
.
IteratorFreeFunction
type C_IteratorFreeFunction = Ptr Iterator -> IO () Source #
Type for the callback on the (unwrapped) C side.
type IteratorFreeFunction Source #
This function will be called when the iterator is freed.
Implementors of a Iterator
should implement this
function and pass it to the constructor of the custom iterator.
The function will be called with the iterator lock held.
dynamic_IteratorFreeFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_IteratorFreeFunction | |
-> Iterator |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IteratorFreeFunction :: MonadIO m => IteratorFreeFunction -> m (GClosure C_IteratorFreeFunction) Source #
Wrap the callback into a GClosure
.
mk_IteratorFreeFunction :: C_IteratorFreeFunction -> IO (FunPtr C_IteratorFreeFunction) Source #
Generate a function pointer callable from C code, from a C_IteratorFreeFunction
.
noIteratorFreeFunction :: Maybe IteratorFreeFunction Source #
A convenience synonym for
.Nothing
:: Maybe
IteratorFreeFunction
wrap_IteratorFreeFunction :: Maybe (Ptr (FunPtr C_IteratorFreeFunction)) -> IteratorFreeFunction -> C_IteratorFreeFunction Source #
Wrap a IteratorFreeFunction
into a C_IteratorFreeFunction
.
IteratorItemFunction
type C_IteratorItemFunction = Ptr Iterator -> Ptr GValue -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type IteratorItemFunction Source #
= Iterator |
|
-> GValue |
|
-> IO IteratorItem | Returns: the result of the operation. |
The function that will be called after the next item of the iterator has been retrieved. This function can be used to skip items or stop the iterator.
The function will be called with the iterator lock held.
dynamic_IteratorItemFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_IteratorItemFunction | |
-> Iterator |
|
-> GValue |
|
-> m IteratorItem | Returns: the result of the operation. |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IteratorItemFunction :: MonadIO m => IteratorItemFunction -> m (GClosure C_IteratorItemFunction) Source #
Wrap the callback into a GClosure
.
mk_IteratorItemFunction :: C_IteratorItemFunction -> IO (FunPtr C_IteratorItemFunction) Source #
Generate a function pointer callable from C code, from a C_IteratorItemFunction
.
noIteratorItemFunction :: Maybe IteratorItemFunction Source #
A convenience synonym for
.Nothing
:: Maybe
IteratorItemFunction
wrap_IteratorItemFunction :: Maybe (Ptr (FunPtr C_IteratorItemFunction)) -> IteratorItemFunction -> C_IteratorItemFunction Source #
Wrap a IteratorItemFunction
into a C_IteratorItemFunction
.
IteratorNextFunction
type C_IteratorNextFunction = Ptr Iterator -> Ptr GValue -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type IteratorNextFunction Source #
= Iterator |
|
-> GValue |
|
-> IO IteratorResult | Returns: the result of the operation. |
The function that will be called when the next element of the iterator should be retrieved.
Implementors of a Iterator
should implement this
function and pass it to the constructor of the custom iterator.
The function will be called with the iterator lock held.
dynamic_IteratorNextFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_IteratorNextFunction | |
-> Iterator |
|
-> GValue |
|
-> m IteratorResult | Returns: the result of the operation. |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IteratorNextFunction :: MonadIO m => IteratorNextFunction -> m (GClosure C_IteratorNextFunction) Source #
Wrap the callback into a GClosure
.
mk_IteratorNextFunction :: C_IteratorNextFunction -> IO (FunPtr C_IteratorNextFunction) Source #
Generate a function pointer callable from C code, from a C_IteratorNextFunction
.
noIteratorNextFunction :: Maybe IteratorNextFunction Source #
A convenience synonym for
.Nothing
:: Maybe
IteratorNextFunction
wrap_IteratorNextFunction :: Maybe (Ptr (FunPtr C_IteratorNextFunction)) -> IteratorNextFunction -> C_IteratorNextFunction Source #
Wrap a IteratorNextFunction
into a C_IteratorNextFunction
.
IteratorResyncFunction
type C_IteratorResyncFunction = Ptr Iterator -> IO () Source #
Type for the callback on the (unwrapped) C side.
type IteratorResyncFunction Source #
This function will be called whenever a concurrent update happened to the iterated datastructure. The implementor of the iterator should restart the iterator from the beginning and clean up any state it might have.
Implementors of a Iterator
should implement this
function and pass it to the constructor of the custom iterator.
The function will be called with the iterator lock held.
dynamic_IteratorResyncFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_IteratorResyncFunction | |
-> Iterator |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IteratorResyncFunction :: MonadIO m => IteratorResyncFunction -> m (GClosure C_IteratorResyncFunction) Source #
Wrap the callback into a GClosure
.
mk_IteratorResyncFunction :: C_IteratorResyncFunction -> IO (FunPtr C_IteratorResyncFunction) Source #
Generate a function pointer callable from C code, from a C_IteratorResyncFunction
.
noIteratorResyncFunction :: Maybe IteratorResyncFunction Source #
A convenience synonym for
.Nothing
:: Maybe
IteratorResyncFunction
wrap_IteratorResyncFunction :: Maybe (Ptr (FunPtr C_IteratorResyncFunction)) -> IteratorResyncFunction -> C_IteratorResyncFunction Source #
Wrap a IteratorResyncFunction
into a C_IteratorResyncFunction
.
LogFunction
type C_LogFunction = Ptr DebugCategory -> CUInt -> CString -> CString -> Int32 -> Ptr Object -> Ptr DebugMessage -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type LogFunction Source #
= DebugCategory |
|
-> DebugLevel |
|
-> Text |
|
-> Text |
|
-> Int32 |
|
-> Object |
|
-> DebugMessage |
|
-> IO () |
Function prototype for a logging function that can be registered with
debugAddLogFunction
.
Use G_GNUC_NO_INSTRUMENT on that function.
type LogFunction_WithClosures Source #
= DebugCategory |
|
-> DebugLevel |
|
-> Text |
|
-> Text |
|
-> Int32 |
|
-> Object |
|
-> DebugMessage |
|
-> Ptr () |
|
-> IO () |
Function prototype for a logging function that can be registered with
debugAddLogFunction
.
Use G_GNUC_NO_INSTRUMENT on that function.
drop_closures_LogFunction :: LogFunction -> LogFunction_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_LogFunction | |
-> DebugCategory |
|
-> DebugLevel |
|
-> Text |
|
-> Text |
|
-> Int32 |
|
-> a |
|
-> DebugMessage |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_LogFunction :: MonadIO m => LogFunction -> m (GClosure C_LogFunction) Source #
Wrap the callback into a GClosure
.
mk_LogFunction :: C_LogFunction -> IO (FunPtr C_LogFunction) Source #
Generate a function pointer callable from C code, from a C_LogFunction
.
noLogFunction :: Maybe LogFunction Source #
A convenience synonym for
.Nothing
:: Maybe
LogFunction
noLogFunction_WithClosures :: Maybe LogFunction_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
LogFunction_WithClosures
wrap_LogFunction :: Maybe (Ptr (FunPtr C_LogFunction)) -> LogFunction_WithClosures -> C_LogFunction Source #
Wrap a LogFunction
into a C_LogFunction
.
MemoryCopyFunction
type C_MemoryCopyFunction = Ptr Memory -> Int64 -> Int64 -> IO (Ptr Memory) Source #
Type for the callback on the (unwrapped) C side.
type MemoryCopyFunction Source #
= Memory |
|
-> Int64 |
|
-> Int64 |
|
-> IO Memory | Returns: a new |
Copy size
bytes from mem
starting at offset
and return them wrapped in a
new GstMemory object.
If size
is set to -1, all bytes starting at offset
are copied.
dynamic_MemoryCopyFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MemoryCopyFunction | |
-> Memory |
|
-> Int64 |
|
-> Int64 |
|
-> m Memory | Returns: a new |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemoryCopyFunction :: MonadIO m => MemoryCopyFunction -> m (GClosure C_MemoryCopyFunction) Source #
Wrap the callback into a GClosure
.
mk_MemoryCopyFunction :: C_MemoryCopyFunction -> IO (FunPtr C_MemoryCopyFunction) Source #
Generate a function pointer callable from C code, from a C_MemoryCopyFunction
.
noMemoryCopyFunction :: Maybe MemoryCopyFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MemoryCopyFunction
wrap_MemoryCopyFunction :: Maybe (Ptr (FunPtr C_MemoryCopyFunction)) -> MemoryCopyFunction -> C_MemoryCopyFunction Source #
Wrap a MemoryCopyFunction
into a C_MemoryCopyFunction
.
MemoryIsSpanFunction
type C_MemoryIsSpanFunction = Ptr Memory -> Ptr Memory -> Word64 -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type MemoryIsSpanFunction Source #
= Memory |
|
-> Memory |
|
-> Word64 |
|
-> IO Bool | Returns: |
Check if mem1
and mem2
occupy contiguous memory and return the offset of
mem1
in the parent buffer in offset
.
dynamic_MemoryIsSpanFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MemoryIsSpanFunction | |
-> Memory |
|
-> Memory |
|
-> Word64 |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemoryIsSpanFunction :: MonadIO m => MemoryIsSpanFunction -> m (GClosure C_MemoryIsSpanFunction) Source #
Wrap the callback into a GClosure
.
mk_MemoryIsSpanFunction :: C_MemoryIsSpanFunction -> IO (FunPtr C_MemoryIsSpanFunction) Source #
Generate a function pointer callable from C code, from a C_MemoryIsSpanFunction
.
noMemoryIsSpanFunction :: Maybe MemoryIsSpanFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MemoryIsSpanFunction
wrap_MemoryIsSpanFunction :: Maybe (Ptr (FunPtr C_MemoryIsSpanFunction)) -> MemoryIsSpanFunction -> C_MemoryIsSpanFunction Source #
Wrap a MemoryIsSpanFunction
into a C_MemoryIsSpanFunction
.
MemoryMapFullFunction
type C_MemoryMapFullFunction = Ptr Memory -> Ptr MapInfo -> Word64 -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
type MemoryMapFullFunction Source #
= Memory |
|
-> MapInfo |
|
-> Word64 |
|
-> IO (Ptr ()) | Returns: a pointer to memory of which at least |
Get the memory of mem
that can be accessed according to the mode specified
in info
's flags. The function should return a pointer that contains at least
maxsize
bytes.
dynamic_MemoryMapFullFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MemoryMapFullFunction | |
-> Memory |
|
-> MapInfo |
|
-> Word64 |
|
-> m (Ptr ()) | Returns: a pointer to memory of which at least |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemoryMapFullFunction :: MonadIO m => MemoryMapFullFunction -> m (GClosure C_MemoryMapFullFunction) Source #
Wrap the callback into a GClosure
.
mk_MemoryMapFullFunction :: C_MemoryMapFullFunction -> IO (FunPtr C_MemoryMapFullFunction) Source #
Generate a function pointer callable from C code, from a C_MemoryMapFullFunction
.
noMemoryMapFullFunction :: Maybe MemoryMapFullFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MemoryMapFullFunction
wrap_MemoryMapFullFunction :: Maybe (Ptr (FunPtr C_MemoryMapFullFunction)) -> MemoryMapFullFunction -> C_MemoryMapFullFunction Source #
Wrap a MemoryMapFullFunction
into a C_MemoryMapFullFunction
.
MemoryMapFunction
type C_MemoryMapFunction = Ptr Memory -> Word64 -> CUInt -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
type MemoryMapFunction Source #
= Memory |
|
-> Word64 |
|
-> [MapFlags] |
|
-> IO (Ptr ()) | Returns: a pointer to memory of which at least |
Get the memory of mem
that can be accessed according to the mode specified
in flags
. The function should return a pointer that contains at least
maxsize
bytes.
dynamic_MemoryMapFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MemoryMapFunction | |
-> Memory |
|
-> Word64 |
|
-> [MapFlags] |
|
-> m (Ptr ()) | Returns: a pointer to memory of which at least |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemoryMapFunction :: MonadIO m => MemoryMapFunction -> m (GClosure C_MemoryMapFunction) Source #
Wrap the callback into a GClosure
.
mk_MemoryMapFunction :: C_MemoryMapFunction -> IO (FunPtr C_MemoryMapFunction) Source #
Generate a function pointer callable from C code, from a C_MemoryMapFunction
.
noMemoryMapFunction :: Maybe MemoryMapFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MemoryMapFunction
wrap_MemoryMapFunction :: Maybe (Ptr (FunPtr C_MemoryMapFunction)) -> MemoryMapFunction -> C_MemoryMapFunction Source #
Wrap a MemoryMapFunction
into a C_MemoryMapFunction
.
MemoryShareFunction
type C_MemoryShareFunction = Ptr Memory -> Int64 -> Int64 -> IO (Ptr Memory) Source #
Type for the callback on the (unwrapped) C side.
type MemoryShareFunction Source #
= Memory |
|
-> Int64 |
|
-> Int64 |
|
-> IO Memory | Returns: a new |
Share size
bytes from mem
starting at offset
and return them wrapped in a
new GstMemory object. If size
is set to -1, all bytes starting at offset
are
shared. This function does not make a copy of the bytes in mem
.
dynamic_MemoryShareFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MemoryShareFunction | |
-> Memory |
|
-> Int64 |
|
-> Int64 |
|
-> m Memory | Returns: a new |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemoryShareFunction :: MonadIO m => MemoryShareFunction -> m (GClosure C_MemoryShareFunction) Source #
Wrap the callback into a GClosure
.
mk_MemoryShareFunction :: C_MemoryShareFunction -> IO (FunPtr C_MemoryShareFunction) Source #
Generate a function pointer callable from C code, from a C_MemoryShareFunction
.
noMemoryShareFunction :: Maybe MemoryShareFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MemoryShareFunction
wrap_MemoryShareFunction :: Maybe (Ptr (FunPtr C_MemoryShareFunction)) -> MemoryShareFunction -> C_MemoryShareFunction Source #
Wrap a MemoryShareFunction
into a C_MemoryShareFunction
.
MemoryUnmapFullFunction
type C_MemoryUnmapFullFunction = Ptr Memory -> Ptr MapInfo -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MemoryUnmapFullFunction Source #
Return the pointer previously retrieved with memoryMap
with info
.
dynamic_MemoryUnmapFullFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MemoryUnmapFullFunction | |
-> Memory |
|
-> MapInfo |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemoryUnmapFullFunction :: MonadIO m => MemoryUnmapFullFunction -> m (GClosure C_MemoryUnmapFullFunction) Source #
Wrap the callback into a GClosure
.
mk_MemoryUnmapFullFunction :: C_MemoryUnmapFullFunction -> IO (FunPtr C_MemoryUnmapFullFunction) Source #
Generate a function pointer callable from C code, from a C_MemoryUnmapFullFunction
.
noMemoryUnmapFullFunction :: Maybe MemoryUnmapFullFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MemoryUnmapFullFunction
wrap_MemoryUnmapFullFunction :: Maybe (Ptr (FunPtr C_MemoryUnmapFullFunction)) -> MemoryUnmapFullFunction -> C_MemoryUnmapFullFunction Source #
Wrap a MemoryUnmapFullFunction
into a C_MemoryUnmapFullFunction
.
MemoryUnmapFunction
type C_MemoryUnmapFunction = Ptr Memory -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MemoryUnmapFunction Source #
Return the pointer previously retrieved with memoryMap
.
dynamic_MemoryUnmapFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MemoryUnmapFunction | |
-> Memory |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MemoryUnmapFunction :: MonadIO m => MemoryUnmapFunction -> m (GClosure C_MemoryUnmapFunction) Source #
Wrap the callback into a GClosure
.
mk_MemoryUnmapFunction :: C_MemoryUnmapFunction -> IO (FunPtr C_MemoryUnmapFunction) Source #
Generate a function pointer callable from C code, from a C_MemoryUnmapFunction
.
noMemoryUnmapFunction :: Maybe MemoryUnmapFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MemoryUnmapFunction
wrap_MemoryUnmapFunction :: Maybe (Ptr (FunPtr C_MemoryUnmapFunction)) -> MemoryUnmapFunction -> C_MemoryUnmapFunction Source #
Wrap a MemoryUnmapFunction
into a C_MemoryUnmapFunction
.
MetaFreeFunction
type C_MetaFreeFunction = Ptr Meta -> Ptr Buffer -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MetaFreeFunction Source #
Function called when meta
is freed in buffer
.
dynamic_MetaFreeFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MetaFreeFunction | |
-> Meta |
|
-> Buffer |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MetaFreeFunction :: MonadIO m => MetaFreeFunction -> m (GClosure C_MetaFreeFunction) Source #
Wrap the callback into a GClosure
.
mk_MetaFreeFunction :: C_MetaFreeFunction -> IO (FunPtr C_MetaFreeFunction) Source #
Generate a function pointer callable from C code, from a C_MetaFreeFunction
.
noMetaFreeFunction :: Maybe MetaFreeFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MetaFreeFunction
wrap_MetaFreeFunction :: Maybe (Ptr (FunPtr C_MetaFreeFunction)) -> MetaFreeFunction -> C_MetaFreeFunction Source #
Wrap a MetaFreeFunction
into a C_MetaFreeFunction
.
MetaInitFunction
type C_MetaInitFunction = Ptr Meta -> Ptr () -> Ptr Buffer -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type MetaInitFunction Source #
= Meta |
|
-> Ptr () |
|
-> Buffer |
|
-> IO Bool |
Function called when meta
is initialized in buffer
.
dynamic_MetaInitFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MetaInitFunction | |
-> Meta |
|
-> Ptr () |
|
-> Buffer |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MetaInitFunction :: MonadIO m => MetaInitFunction -> m (GClosure C_MetaInitFunction) Source #
Wrap the callback into a GClosure
.
mk_MetaInitFunction :: C_MetaInitFunction -> IO (FunPtr C_MetaInitFunction) Source #
Generate a function pointer callable from C code, from a C_MetaInitFunction
.
noMetaInitFunction :: Maybe MetaInitFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MetaInitFunction
wrap_MetaInitFunction :: Maybe (Ptr (FunPtr C_MetaInitFunction)) -> MetaInitFunction -> C_MetaInitFunction Source #
Wrap a MetaInitFunction
into a C_MetaInitFunction
.
MetaTransformFunction
type C_MetaTransformFunction = Ptr Buffer -> Ptr Meta -> Ptr Buffer -> Word32 -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type MetaTransformFunction Source #
= Buffer |
|
-> Meta |
|
-> Buffer |
|
-> Word32 |
|
-> Ptr () |
|
-> IO Bool | Returns: |
Function called for each meta
in buffer
as a result of performing a
transformation on transbuf
. Additional type
specific transform data
is passed to the function as data
.
Implementations should check the type
of the transform and parse
additional type specific fields in data
that should be used to update
the metadata on transbuf
.
dynamic_MetaTransformFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MetaTransformFunction | |
-> Buffer |
|
-> Meta |
|
-> Buffer |
|
-> Word32 |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MetaTransformFunction :: MonadIO m => MetaTransformFunction -> m (GClosure C_MetaTransformFunction) Source #
Wrap the callback into a GClosure
.
mk_MetaTransformFunction :: C_MetaTransformFunction -> IO (FunPtr C_MetaTransformFunction) Source #
Generate a function pointer callable from C code, from a C_MetaTransformFunction
.
noMetaTransformFunction :: Maybe MetaTransformFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MetaTransformFunction
wrap_MetaTransformFunction :: Maybe (Ptr (FunPtr C_MetaTransformFunction)) -> MetaTransformFunction -> C_MetaTransformFunction Source #
Wrap a MetaTransformFunction
into a C_MetaTransformFunction
.
MiniObjectDisposeFunction
type C_MiniObjectDisposeFunction = Ptr MiniObject -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type MiniObjectDisposeFunction Source #
= MiniObject |
|
-> IO Bool | Returns: |
Function prototype for when a miniobject has lost its last refcount.
Implementation of the mini object are allowed to revive the
passed object by doing a gst_mini_object_ref()
. If the object is not
revived after the dispose function, the function should return True
and the memory associated with the object is freed.
dynamic_MiniObjectDisposeFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MiniObjectDisposeFunction | |
-> MiniObject |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MiniObjectDisposeFunction :: MonadIO m => MiniObjectDisposeFunction -> m (GClosure C_MiniObjectDisposeFunction) Source #
Wrap the callback into a GClosure
.
mk_MiniObjectDisposeFunction :: C_MiniObjectDisposeFunction -> IO (FunPtr C_MiniObjectDisposeFunction) Source #
Generate a function pointer callable from C code, from a C_MiniObjectDisposeFunction
.
noMiniObjectDisposeFunction :: Maybe MiniObjectDisposeFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MiniObjectDisposeFunction
wrap_MiniObjectDisposeFunction :: Maybe (Ptr (FunPtr C_MiniObjectDisposeFunction)) -> MiniObjectDisposeFunction -> C_MiniObjectDisposeFunction Source #
Wrap a MiniObjectDisposeFunction
into a C_MiniObjectDisposeFunction
.
MiniObjectFreeFunction
type C_MiniObjectFreeFunction = Ptr MiniObject -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MiniObjectFreeFunction Source #
= MiniObject |
|
-> IO () |
Virtual function prototype for methods to free resources used by mini-objects.
dynamic_MiniObjectFreeFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MiniObjectFreeFunction | |
-> MiniObject |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MiniObjectFreeFunction :: MonadIO m => MiniObjectFreeFunction -> m (GClosure C_MiniObjectFreeFunction) Source #
Wrap the callback into a GClosure
.
mk_MiniObjectFreeFunction :: C_MiniObjectFreeFunction -> IO (FunPtr C_MiniObjectFreeFunction) Source #
Generate a function pointer callable from C code, from a C_MiniObjectFreeFunction
.
noMiniObjectFreeFunction :: Maybe MiniObjectFreeFunction Source #
A convenience synonym for
.Nothing
:: Maybe
MiniObjectFreeFunction
wrap_MiniObjectFreeFunction :: Maybe (Ptr (FunPtr C_MiniObjectFreeFunction)) -> MiniObjectFreeFunction -> C_MiniObjectFreeFunction Source #
Wrap a MiniObjectFreeFunction
into a C_MiniObjectFreeFunction
.
MiniObjectNotify
type C_MiniObjectNotify = Ptr () -> Ptr MiniObject -> IO () Source #
Type for the callback on the (unwrapped) C side.
type MiniObjectNotify Source #
= MiniObject |
|
-> IO () |
A MiniObjectNotify
function can be added to a mini object as a
callback that gets triggered when gst_mini_object_unref()
drops the
last ref and obj
is about to be freed.
type MiniObjectNotify_WithClosures Source #
= Ptr () |
|
-> MiniObject |
|
-> IO () |
A MiniObjectNotify
function can be added to a mini object as a
callback that gets triggered when gst_mini_object_unref()
drops the
last ref and obj
is about to be freed.
drop_closures_MiniObjectNotify :: MiniObjectNotify -> MiniObjectNotify_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_MiniObjectNotify Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_MiniObjectNotify | |
-> Ptr () |
|
-> MiniObject |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_MiniObjectNotify :: MonadIO m => MiniObjectNotify -> m (GClosure C_MiniObjectNotify) Source #
Wrap the callback into a GClosure
.
mk_MiniObjectNotify :: C_MiniObjectNotify -> IO (FunPtr C_MiniObjectNotify) Source #
Generate a function pointer callable from C code, from a C_MiniObjectNotify
.
noMiniObjectNotify :: Maybe MiniObjectNotify Source #
A convenience synonym for
.Nothing
:: Maybe
MiniObjectNotify
noMiniObjectNotify_WithClosures :: Maybe MiniObjectNotify_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
MiniObjectNotify_WithClosures
wrap_MiniObjectNotify :: Maybe (Ptr (FunPtr C_MiniObjectNotify)) -> MiniObjectNotify_WithClosures -> C_MiniObjectNotify Source #
Wrap a MiniObjectNotify
into a C_MiniObjectNotify
.
PadActivateFunction
type C_PadActivateFunction = Ptr Pad -> Ptr Object -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadActivateFunction Source #
= Pad |
|
-> Object |
|
-> IO Bool | Returns: |
This function is called when the pad is activated during the element READY to PAUSED state change. By default this function will call the activate function that puts the pad in push mode but elements can override this function to activate the pad in pull mode if they wish.
dynamic_PadActivateFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadActivateFunction | |
-> a |
|
-> b |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadActivateFunction :: MonadIO m => PadActivateFunction -> m (GClosure C_PadActivateFunction) Source #
Wrap the callback into a GClosure
.
mk_PadActivateFunction :: C_PadActivateFunction -> IO (FunPtr C_PadActivateFunction) Source #
Generate a function pointer callable from C code, from a C_PadActivateFunction
.
noPadActivateFunction :: Maybe PadActivateFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadActivateFunction
wrap_PadActivateFunction :: Maybe (Ptr (FunPtr C_PadActivateFunction)) -> PadActivateFunction -> C_PadActivateFunction Source #
Wrap a PadActivateFunction
into a C_PadActivateFunction
.
PadActivateModeFunction
type C_PadActivateModeFunction = Ptr Pad -> Ptr Object -> CUInt -> CInt -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadActivateModeFunction Source #
= Pad |
|
-> Object |
|
-> PadMode |
|
-> Bool |
|
-> IO Bool | Returns: |
The prototype of the push and pull activate functions.
dynamic_PadActivateModeFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadActivateModeFunction | |
-> a |
|
-> b |
|
-> PadMode |
|
-> Bool |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadActivateModeFunction :: MonadIO m => PadActivateModeFunction -> m (GClosure C_PadActivateModeFunction) Source #
Wrap the callback into a GClosure
.
mk_PadActivateModeFunction :: C_PadActivateModeFunction -> IO (FunPtr C_PadActivateModeFunction) Source #
Generate a function pointer callable from C code, from a C_PadActivateModeFunction
.
noPadActivateModeFunction :: Maybe PadActivateModeFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadActivateModeFunction
wrap_PadActivateModeFunction :: Maybe (Ptr (FunPtr C_PadActivateModeFunction)) -> PadActivateModeFunction -> C_PadActivateModeFunction Source #
Wrap a PadActivateModeFunction
into a C_PadActivateModeFunction
.
PadChainFunction
type C_PadChainFunction = Ptr Pad -> Ptr Object -> Ptr Buffer -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadChainFunction Source #
= Pad |
|
-> Maybe Object |
|
-> Buffer | |
-> IO FlowReturn | Returns: |
A function that will be called on sinkpads when chaining buffers. The function typically processes the data contained in the buffer and either consumes the data or passes it on to the internally linked pad(s).
The implementer of this function receives a refcount to buffer
and should
gst_buffer_unref()
when the buffer is no longer needed.
When a chain function detects an error in the data stream, it must post an
error on the bus and return an appropriate FlowReturn
value.
dynamic_PadChainFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadChainFunction | |
-> a |
|
-> Maybe b |
|
-> Buffer | |
-> m FlowReturn | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadChainFunction :: MonadIO m => PadChainFunction -> m (GClosure C_PadChainFunction) Source #
Wrap the callback into a GClosure
.
mk_PadChainFunction :: C_PadChainFunction -> IO (FunPtr C_PadChainFunction) Source #
Generate a function pointer callable from C code, from a C_PadChainFunction
.
noPadChainFunction :: Maybe PadChainFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadChainFunction
wrap_PadChainFunction :: Maybe (Ptr (FunPtr C_PadChainFunction)) -> PadChainFunction -> C_PadChainFunction Source #
Wrap a PadChainFunction
into a C_PadChainFunction
.
PadChainListFunction
type C_PadChainListFunction = Ptr Pad -> Ptr Object -> Ptr BufferList -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadChainListFunction Source #
= Pad |
|
-> Maybe Object |
|
-> BufferList |
|
-> IO FlowReturn | Returns: |
A function that will be called on sinkpads when chaining buffer lists. The function typically processes the data contained in the buffer list and either consumes the data or passes it on to the internally linked pad(s).
The implementer of this function receives a refcount to list
and
should gst_buffer_list_unref()
when the list is no longer needed.
When a chainlist function detects an error in the data stream, it must
post an error on the bus and return an appropriate FlowReturn
value.
dynamic_PadChainListFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadChainListFunction | |
-> a |
|
-> Maybe b |
|
-> BufferList |
|
-> m FlowReturn | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadChainListFunction :: MonadIO m => PadChainListFunction -> m (GClosure C_PadChainListFunction) Source #
Wrap the callback into a GClosure
.
mk_PadChainListFunction :: C_PadChainListFunction -> IO (FunPtr C_PadChainListFunction) Source #
Generate a function pointer callable from C code, from a C_PadChainListFunction
.
noPadChainListFunction :: Maybe PadChainListFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadChainListFunction
wrap_PadChainListFunction :: Maybe (Ptr (FunPtr C_PadChainListFunction)) -> PadChainListFunction -> C_PadChainListFunction Source #
Wrap a PadChainListFunction
into a C_PadChainListFunction
.
PadEventFullFunction
type C_PadEventFullFunction = Ptr Pad -> Ptr Object -> Ptr Event -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadEventFullFunction Source #
= Pad |
|
-> Maybe Object |
|
-> Event |
|
-> IO FlowReturn | Returns: |
Function signature to handle an event for the pad.
This variant is for specific elements that will take into account the last downstream flow return (from a pad push), in which case they can return it.
Since: 1.8
dynamic_PadEventFullFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadEventFullFunction | |
-> a |
|
-> Maybe b |
|
-> Event |
|
-> m FlowReturn | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadEventFullFunction :: MonadIO m => PadEventFullFunction -> m (GClosure C_PadEventFullFunction) Source #
Wrap the callback into a GClosure
.
mk_PadEventFullFunction :: C_PadEventFullFunction -> IO (FunPtr C_PadEventFullFunction) Source #
Generate a function pointer callable from C code, from a C_PadEventFullFunction
.
noPadEventFullFunction :: Maybe PadEventFullFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadEventFullFunction
wrap_PadEventFullFunction :: Maybe (Ptr (FunPtr C_PadEventFullFunction)) -> PadEventFullFunction -> C_PadEventFullFunction Source #
Wrap a PadEventFullFunction
into a C_PadEventFullFunction
.
PadEventFunction
type C_PadEventFunction = Ptr Pad -> Ptr Object -> Ptr Event -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadEventFunction Source #
= Pad |
|
-> Maybe Object |
|
-> Event |
|
-> IO Bool | Returns: |
Function signature to handle an event for the pad.
dynamic_PadEventFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadEventFunction | |
-> a |
|
-> Maybe b |
|
-> Event |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadEventFunction :: MonadIO m => PadEventFunction -> m (GClosure C_PadEventFunction) Source #
Wrap the callback into a GClosure
.
mk_PadEventFunction :: C_PadEventFunction -> IO (FunPtr C_PadEventFunction) Source #
Generate a function pointer callable from C code, from a C_PadEventFunction
.
noPadEventFunction :: Maybe PadEventFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadEventFunction
wrap_PadEventFunction :: Maybe (Ptr (FunPtr C_PadEventFunction)) -> PadEventFunction -> C_PadEventFunction Source #
Wrap a PadEventFunction
into a C_PadEventFunction
.
PadForwardFunction
type C_PadForwardFunction = Ptr Pad -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadForwardFunction Source #
= Pad |
|
-> IO Bool | Returns: |
A forward function is called for all internally linked pads, see
padForward
.
type PadForwardFunction_WithClosures Source #
= Pad |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A forward function is called for all internally linked pads, see
padForward
.
drop_closures_PadForwardFunction :: PadForwardFunction -> PadForwardFunction_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_PadForwardFunction Source #
:: (HasCallStack, MonadIO m, IsPad a) | |
=> FunPtr C_PadForwardFunction | |
-> a |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadForwardFunction :: MonadIO m => PadForwardFunction -> m (GClosure C_PadForwardFunction) Source #
Wrap the callback into a GClosure
.
mk_PadForwardFunction :: C_PadForwardFunction -> IO (FunPtr C_PadForwardFunction) Source #
Generate a function pointer callable from C code, from a C_PadForwardFunction
.
noPadForwardFunction :: Maybe PadForwardFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadForwardFunction
noPadForwardFunction_WithClosures :: Maybe PadForwardFunction_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PadForwardFunction_WithClosures
wrap_PadForwardFunction :: Maybe (Ptr (FunPtr C_PadForwardFunction)) -> PadForwardFunction_WithClosures -> C_PadForwardFunction Source #
Wrap a PadForwardFunction
into a C_PadForwardFunction
.
PadGetRangeFunction
type C_PadGetRangeFunction = Ptr Pad -> Ptr Object -> Word64 -> Word32 -> Ptr Buffer -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadGetRangeFunction Source #
= Pad |
|
-> Maybe Object |
|
-> Word64 |
|
-> Word32 |
|
-> Buffer |
|
-> IO FlowReturn | Returns: |
This function will be called on source pads when a peer element
request a buffer at the specified offset
and length
. If this function
returns GST_FLOW_OK
, the result buffer will be stored in buffer
. The
contents of buffer
is invalid for any other return value.
This function is installed on a source pad with
gst_pad_set_getrange_function()
and can only be called on source pads after
they are successfully activated with padActivateMode
with the
GST_PAD_MODE_PULL
.
offset
and length
are always given in byte units. offset
must normally be a value
between 0 and the length in bytes of the data available on pad
. The
length (duration in bytes) can be retrieved with a GST_QUERY_DURATION
or with a
GST_QUERY_SEEKING
.
Any offset
larger or equal than the length will make the function return
GST_FLOW_EOS
, which corresponds to EOS. In this case buffer
does not
contain a valid buffer.
The buffer size of buffer
will only be smaller than length
when offset
is
near the end of the stream. In all other cases, the size of buffer
must be
exactly the requested size.
It is allowed to call this function with a 0 length
and valid offset
, in
which case buffer
will contain a 0-sized buffer and the function returns
GST_FLOW_OK
.
When this function is called with a -1 offset
, the sequentially next buffer
of length length
in the stream is returned.
When this function is called with a -1 length
, a buffer with a default
optimal length is returned in buffer
. The length might depend on the value
of offset
.
dynamic_PadGetRangeFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadGetRangeFunction | |
-> a |
|
-> Maybe b |
|
-> Word64 |
|
-> Word32 |
|
-> Buffer |
|
-> m FlowReturn | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadGetRangeFunction :: MonadIO m => PadGetRangeFunction -> m (GClosure C_PadGetRangeFunction) Source #
Wrap the callback into a GClosure
.
mk_PadGetRangeFunction :: C_PadGetRangeFunction -> IO (FunPtr C_PadGetRangeFunction) Source #
Generate a function pointer callable from C code, from a C_PadGetRangeFunction
.
noPadGetRangeFunction :: Maybe PadGetRangeFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadGetRangeFunction
wrap_PadGetRangeFunction :: Maybe (Ptr (FunPtr C_PadGetRangeFunction)) -> PadGetRangeFunction -> C_PadGetRangeFunction Source #
Wrap a PadGetRangeFunction
into a C_PadGetRangeFunction
.
PadIterIntLinkFunction
type C_PadIterIntLinkFunction = Ptr Pad -> Ptr Object -> IO (Ptr Iterator) Source #
Type for the callback on the (unwrapped) C side.
type PadIterIntLinkFunction Source #
= Pad |
|
-> Maybe Object |
|
-> IO Iterator | Returns: a new the caller must call |
The signature of the internal pad link iterator function.
dynamic_PadIterIntLinkFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadIterIntLinkFunction | |
-> a |
|
-> Maybe b |
|
-> m Iterator | Returns: a new the caller must call |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadIterIntLinkFunction :: MonadIO m => PadIterIntLinkFunction -> m (GClosure C_PadIterIntLinkFunction) Source #
Wrap the callback into a GClosure
.
mk_PadIterIntLinkFunction :: C_PadIterIntLinkFunction -> IO (FunPtr C_PadIterIntLinkFunction) Source #
Generate a function pointer callable from C code, from a C_PadIterIntLinkFunction
.
noPadIterIntLinkFunction :: Maybe PadIterIntLinkFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadIterIntLinkFunction
wrap_PadIterIntLinkFunction :: Maybe (Ptr (FunPtr C_PadIterIntLinkFunction)) -> PadIterIntLinkFunction -> C_PadIterIntLinkFunction Source #
Wrap a PadIterIntLinkFunction
into a C_PadIterIntLinkFunction
.
PadLinkFunction
type C_PadLinkFunction = Ptr Pad -> Ptr Object -> Ptr Pad -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadLinkFunction Source #
= Pad |
|
-> Maybe Object |
|
-> Pad |
|
-> IO PadLinkReturn | Returns: the result of the link with the specified peer. |
Function signature to handle a new link on the pad.
dynamic_PadLinkFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b, IsPad c) | |
=> FunPtr C_PadLinkFunction | |
-> a |
|
-> Maybe b |
|
-> c |
|
-> m PadLinkReturn | Returns: the result of the link with the specified peer. |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadLinkFunction :: MonadIO m => PadLinkFunction -> m (GClosure C_PadLinkFunction) Source #
Wrap the callback into a GClosure
.
mk_PadLinkFunction :: C_PadLinkFunction -> IO (FunPtr C_PadLinkFunction) Source #
Generate a function pointer callable from C code, from a C_PadLinkFunction
.
noPadLinkFunction :: Maybe PadLinkFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadLinkFunction
wrap_PadLinkFunction :: Maybe (Ptr (FunPtr C_PadLinkFunction)) -> PadLinkFunction -> C_PadLinkFunction Source #
Wrap a PadLinkFunction
into a C_PadLinkFunction
.
PadProbeCallback
type C_PadProbeCallback = Ptr Pad -> Ptr PadProbeInfo -> Ptr () -> IO CUInt Source #
Type for the callback on the (unwrapped) C side.
type PadProbeCallback Source #
= Pad |
|
-> PadProbeInfo |
|
-> IO PadProbeReturn | Returns: a |
Callback used by padAddProbe
. Gets called to notify about the current
blocking type.
The callback is allowed to modify the data pointer in info
.
type PadProbeCallback_WithClosures Source #
= Pad |
|
-> PadProbeInfo |
|
-> Ptr () |
|
-> IO PadProbeReturn | Returns: a |
Callback used by padAddProbe
. Gets called to notify about the current
blocking type.
The callback is allowed to modify the data pointer in info
.
drop_closures_PadProbeCallback :: PadProbeCallback -> PadProbeCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_PadProbeCallback Source #
:: (HasCallStack, MonadIO m, IsPad a) | |
=> FunPtr C_PadProbeCallback | |
-> a |
|
-> PadProbeInfo |
|
-> Ptr () |
|
-> m PadProbeReturn | Returns: a |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadProbeCallback :: MonadIO m => PadProbeCallback -> m (GClosure C_PadProbeCallback) Source #
Wrap the callback into a GClosure
.
mk_PadProbeCallback :: C_PadProbeCallback -> IO (FunPtr C_PadProbeCallback) Source #
Generate a function pointer callable from C code, from a C_PadProbeCallback
.
noPadProbeCallback :: Maybe PadProbeCallback Source #
A convenience synonym for
.Nothing
:: Maybe
PadProbeCallback
noPadProbeCallback_WithClosures :: Maybe PadProbeCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PadProbeCallback_WithClosures
wrap_PadProbeCallback :: Maybe (Ptr (FunPtr C_PadProbeCallback)) -> PadProbeCallback_WithClosures -> C_PadProbeCallback Source #
Wrap a PadProbeCallback
into a C_PadProbeCallback
.
PadQueryFunction
type C_PadQueryFunction = Ptr Pad -> Ptr Object -> Ptr Query -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadQueryFunction Source #
= Pad |
|
-> Maybe Object |
|
-> Query |
|
-> IO Bool | Returns: |
The signature of the query function.
dynamic_PadQueryFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadQueryFunction | |
-> a |
|
-> Maybe b |
|
-> Query |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadQueryFunction :: MonadIO m => PadQueryFunction -> m (GClosure C_PadQueryFunction) Source #
Wrap the callback into a GClosure
.
mk_PadQueryFunction :: C_PadQueryFunction -> IO (FunPtr C_PadQueryFunction) Source #
Generate a function pointer callable from C code, from a C_PadQueryFunction
.
noPadQueryFunction :: Maybe PadQueryFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadQueryFunction
wrap_PadQueryFunction :: Maybe (Ptr (FunPtr C_PadQueryFunction)) -> PadQueryFunction -> C_PadQueryFunction Source #
Wrap a PadQueryFunction
into a C_PadQueryFunction
.
PadStickyEventsForeachFunction
type C_PadStickyEventsForeachFunction = Ptr Pad -> Ptr Event -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PadStickyEventsForeachFunction Source #
= Pad |
|
-> Maybe Event |
|
-> IO Bool | Returns: |
Callback used by padStickyEventsForeach
.
When this function returns True
, the next event will be
returned. When False
is returned, padStickyEventsForeach
will return.
When event
is set to Nothing
, the item will be removed from the list of sticky events.
event
can be replaced by assigning a new reference to it.
This function is responsible for unreffing the old event when
removing or modifying.
type PadStickyEventsForeachFunction_WithClosures Source #
= Pad |
|
-> Maybe Event |
|
-> Ptr () |
|
-> IO Bool | Returns: |
Callback used by padStickyEventsForeach
.
When this function returns True
, the next event will be
returned. When False
is returned, padStickyEventsForeach
will return.
When event
is set to Nothing
, the item will be removed from the list of sticky events.
event
can be replaced by assigning a new reference to it.
This function is responsible for unreffing the old event when
removing or modifying.
drop_closures_PadStickyEventsForeachFunction :: PadStickyEventsForeachFunction -> PadStickyEventsForeachFunction_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_PadStickyEventsForeachFunction Source #
:: (HasCallStack, MonadIO m, IsPad a) | |
=> FunPtr C_PadStickyEventsForeachFunction | |
-> a |
|
-> Maybe Event |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadStickyEventsForeachFunction :: MonadIO m => PadStickyEventsForeachFunction -> m (GClosure C_PadStickyEventsForeachFunction) Source #
Wrap the callback into a GClosure
.
mk_PadStickyEventsForeachFunction :: C_PadStickyEventsForeachFunction -> IO (FunPtr C_PadStickyEventsForeachFunction) Source #
Generate a function pointer callable from C code, from a C_PadStickyEventsForeachFunction
.
noPadStickyEventsForeachFunction :: Maybe PadStickyEventsForeachFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadStickyEventsForeachFunction
noPadStickyEventsForeachFunction_WithClosures :: Maybe PadStickyEventsForeachFunction_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PadStickyEventsForeachFunction_WithClosures
wrap_PadStickyEventsForeachFunction :: Maybe (Ptr (FunPtr C_PadStickyEventsForeachFunction)) -> PadStickyEventsForeachFunction_WithClosures -> C_PadStickyEventsForeachFunction Source #
Wrap a PadStickyEventsForeachFunction
into a C_PadStickyEventsForeachFunction
.
PadUnlinkFunction
type C_PadUnlinkFunction = Ptr Pad -> Ptr Object -> IO () Source #
Type for the callback on the (unwrapped) C side.
type PadUnlinkFunction Source #
= Pad |
|
-> Maybe Object |
|
-> IO () |
Function signature to handle a unlinking the pad prom its peer.
The pad's lock is already held when the unlink function is called, so most pad functions cannot be called from within the callback.
dynamic_PadUnlinkFunction Source #
:: (HasCallStack, MonadIO m, IsPad a, IsObject b) | |
=> FunPtr C_PadUnlinkFunction | |
-> a |
|
-> Maybe b |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PadUnlinkFunction :: MonadIO m => PadUnlinkFunction -> m (GClosure C_PadUnlinkFunction) Source #
Wrap the callback into a GClosure
.
mk_PadUnlinkFunction :: C_PadUnlinkFunction -> IO (FunPtr C_PadUnlinkFunction) Source #
Generate a function pointer callable from C code, from a C_PadUnlinkFunction
.
noPadUnlinkFunction :: Maybe PadUnlinkFunction Source #
A convenience synonym for
.Nothing
:: Maybe
PadUnlinkFunction
wrap_PadUnlinkFunction :: Maybe (Ptr (FunPtr C_PadUnlinkFunction)) -> PadUnlinkFunction -> C_PadUnlinkFunction Source #
Wrap a PadUnlinkFunction
into a C_PadUnlinkFunction
.
PluginFeatureFilter
type C_PluginFeatureFilter = Ptr PluginFeature -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PluginFeatureFilter Source #
= PluginFeature |
|
-> IO Bool |
A function that can be used with e.g. registryFeatureFilter
to get a list of pluginfeature that match certain criteria.
type PluginFeatureFilter_WithClosures Source #
= PluginFeature |
|
-> Ptr () |
|
-> IO Bool |
A function that can be used with e.g. registryFeatureFilter
to get a list of pluginfeature that match certain criteria.
drop_closures_PluginFeatureFilter :: PluginFeatureFilter -> PluginFeatureFilter_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_PluginFeatureFilter Source #
:: (HasCallStack, MonadIO m, IsPluginFeature a) | |
=> FunPtr C_PluginFeatureFilter | |
-> a |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PluginFeatureFilter :: MonadIO m => PluginFeatureFilter -> m (GClosure C_PluginFeatureFilter) Source #
Wrap the callback into a GClosure
.
mk_PluginFeatureFilter :: C_PluginFeatureFilter -> IO (FunPtr C_PluginFeatureFilter) Source #
Generate a function pointer callable from C code, from a C_PluginFeatureFilter
.
noPluginFeatureFilter :: Maybe PluginFeatureFilter Source #
A convenience synonym for
.Nothing
:: Maybe
PluginFeatureFilter
noPluginFeatureFilter_WithClosures :: Maybe PluginFeatureFilter_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PluginFeatureFilter_WithClosures
wrap_PluginFeatureFilter :: Maybe (Ptr (FunPtr C_PluginFeatureFilter)) -> PluginFeatureFilter_WithClosures -> C_PluginFeatureFilter Source #
Wrap a PluginFeatureFilter
into a C_PluginFeatureFilter
.
PluginFilter
type C_PluginFilter = Ptr Plugin -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PluginFilter Source #
A function that can be used with e.g. registryPluginFilter
to get a list of plugins that match certain criteria.
type PluginFilter_WithClosures Source #
= Plugin |
|
-> Ptr () |
|
-> IO Bool |
A function that can be used with e.g. registryPluginFilter
to get a list of plugins that match certain criteria.
drop_closures_PluginFilter :: PluginFilter -> PluginFilter_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m, IsPlugin a) | |
=> FunPtr C_PluginFilter | |
-> a |
|
-> Ptr () |
|
-> m Bool |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PluginFilter :: MonadIO m => PluginFilter -> m (GClosure C_PluginFilter) Source #
Wrap the callback into a GClosure
.
mk_PluginFilter :: C_PluginFilter -> IO (FunPtr C_PluginFilter) Source #
Generate a function pointer callable from C code, from a C_PluginFilter
.
noPluginFilter :: Maybe PluginFilter Source #
A convenience synonym for
.Nothing
:: Maybe
PluginFilter
noPluginFilter_WithClosures :: Maybe PluginFilter_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PluginFilter_WithClosures
wrap_PluginFilter :: Maybe (Ptr (FunPtr C_PluginFilter)) -> PluginFilter_WithClosures -> C_PluginFilter Source #
Wrap a PluginFilter
into a C_PluginFilter
.
PluginInitFullFunc
type C_PluginInitFullFunc = Ptr Plugin -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PluginInitFullFunc Source #
A plugin should provide a pointer to a function of either PluginInitFunc
or this type in the plugin_desc struct.
The function will be called by the loader at startup. One would then
register each PluginFeature
. This version allows
user data to be passed to init function (useful for bindings).
type PluginInitFullFunc_WithClosures Source #
= Plugin |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A plugin should provide a pointer to a function of either PluginInitFunc
or this type in the plugin_desc struct.
The function will be called by the loader at startup. One would then
register each PluginFeature
. This version allows
user data to be passed to init function (useful for bindings).
drop_closures_PluginInitFullFunc :: PluginInitFullFunc -> PluginInitFullFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_PluginInitFullFunc Source #
:: (HasCallStack, MonadIO m, IsPlugin a) | |
=> FunPtr C_PluginInitFullFunc | |
-> a |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PluginInitFullFunc :: MonadIO m => PluginInitFullFunc -> m (GClosure C_PluginInitFullFunc) Source #
Wrap the callback into a GClosure
.
mk_PluginInitFullFunc :: C_PluginInitFullFunc -> IO (FunPtr C_PluginInitFullFunc) Source #
Generate a function pointer callable from C code, from a C_PluginInitFullFunc
.
noPluginInitFullFunc :: Maybe PluginInitFullFunc Source #
A convenience synonym for
.Nothing
:: Maybe
PluginInitFullFunc
noPluginInitFullFunc_WithClosures :: Maybe PluginInitFullFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PluginInitFullFunc_WithClosures
wrap_PluginInitFullFunc :: Maybe (Ptr (FunPtr C_PluginInitFullFunc)) -> PluginInitFullFunc_WithClosures -> C_PluginInitFullFunc Source #
Wrap a PluginInitFullFunc
into a C_PluginInitFullFunc
.
PluginInitFunc
type C_PluginInitFunc = Ptr Plugin -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PluginInitFunc Source #
A plugin should provide a pointer to a function of this type in the
plugin_desc struct.
This function will be called by the loader at startup. One would then
register each PluginFeature
.
dynamic_PluginInitFunc Source #
:: (HasCallStack, MonadIO m, IsPlugin a) | |
=> FunPtr C_PluginInitFunc | |
-> a |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PluginInitFunc :: MonadIO m => PluginInitFunc -> m (GClosure C_PluginInitFunc) Source #
Wrap the callback into a GClosure
.
mk_PluginInitFunc :: C_PluginInitFunc -> IO (FunPtr C_PluginInitFunc) Source #
Generate a function pointer callable from C code, from a C_PluginInitFunc
.
noPluginInitFunc :: Maybe PluginInitFunc Source #
A convenience synonym for
.Nothing
:: Maybe
PluginInitFunc
wrap_PluginInitFunc :: Maybe (Ptr (FunPtr C_PluginInitFunc)) -> PluginInitFunc -> C_PluginInitFunc Source #
Wrap a PluginInitFunc
into a C_PluginInitFunc
.
PromiseChangeFunc
type C_PromiseChangeFunc = Ptr Promise -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type PromiseChangeFunc Source #
No description available in the introspection data.
Since: 1.14
type PromiseChangeFunc_WithClosures Source #
No description available in the introspection data.
Since: 1.14
drop_closures_PromiseChangeFunc :: PromiseChangeFunc -> PromiseChangeFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_PromiseChangeFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_PromiseChangeFunc | |
-> Promise |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PromiseChangeFunc :: MonadIO m => PromiseChangeFunc -> m (GClosure C_PromiseChangeFunc) Source #
Wrap the callback into a GClosure
.
mk_PromiseChangeFunc :: C_PromiseChangeFunc -> IO (FunPtr C_PromiseChangeFunc) Source #
Generate a function pointer callable from C code, from a C_PromiseChangeFunc
.
noPromiseChangeFunc :: Maybe PromiseChangeFunc Source #
A convenience synonym for
.Nothing
:: Maybe
PromiseChangeFunc
noPromiseChangeFunc_WithClosures :: Maybe PromiseChangeFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PromiseChangeFunc_WithClosures
wrap_PromiseChangeFunc :: Maybe (Ptr (FunPtr C_PromiseChangeFunc)) -> PromiseChangeFunc_WithClosures -> C_PromiseChangeFunc Source #
Wrap a PromiseChangeFunc
into a C_PromiseChangeFunc
.
StructureFilterMapFunc
type C_StructureFilterMapFunc = Word32 -> Ptr GValue -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type StructureFilterMapFunc Source #
= Word32 |
|
-> GValue |
|
-> IO Bool | Returns: |
A function that will be called in structureFilterAndMapInPlace
.
The function may modify value
, and the value will be removed from
the structure if False
is returned.
type StructureFilterMapFunc_WithClosures Source #
= Word32 |
|
-> GValue |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function that will be called in structureFilterAndMapInPlace
.
The function may modify value
, and the value will be removed from
the structure if False
is returned.
drop_closures_StructureFilterMapFunc :: StructureFilterMapFunc -> StructureFilterMapFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_StructureFilterMapFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_StructureFilterMapFunc | |
-> Word32 |
|
-> GValue |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_StructureFilterMapFunc :: MonadIO m => StructureFilterMapFunc -> m (GClosure C_StructureFilterMapFunc) Source #
Wrap the callback into a GClosure
.
mk_StructureFilterMapFunc :: C_StructureFilterMapFunc -> IO (FunPtr C_StructureFilterMapFunc) Source #
Generate a function pointer callable from C code, from a C_StructureFilterMapFunc
.
noStructureFilterMapFunc :: Maybe StructureFilterMapFunc Source #
A convenience synonym for
.Nothing
:: Maybe
StructureFilterMapFunc
noStructureFilterMapFunc_WithClosures :: Maybe StructureFilterMapFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
StructureFilterMapFunc_WithClosures
wrap_StructureFilterMapFunc :: Maybe (Ptr (FunPtr C_StructureFilterMapFunc)) -> StructureFilterMapFunc_WithClosures -> C_StructureFilterMapFunc Source #
Wrap a StructureFilterMapFunc
into a C_StructureFilterMapFunc
.
StructureForeachFunc
type C_StructureForeachFunc = Word32 -> Ptr GValue -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type StructureForeachFunc Source #
= Word32 |
|
-> GValue |
|
-> IO Bool | Returns: |
A function that will be called in structureForeach
. The function may
not modify value
.
type StructureForeachFunc_WithClosures Source #
= Word32 |
|
-> GValue |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function that will be called in structureForeach
. The function may
not modify value
.
drop_closures_StructureForeachFunc :: StructureForeachFunc -> StructureForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_StructureForeachFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_StructureForeachFunc | |
-> Word32 |
|
-> GValue |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_StructureForeachFunc :: MonadIO m => StructureForeachFunc -> m (GClosure C_StructureForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_StructureForeachFunc :: C_StructureForeachFunc -> IO (FunPtr C_StructureForeachFunc) Source #
Generate a function pointer callable from C code, from a C_StructureForeachFunc
.
noStructureForeachFunc :: Maybe StructureForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
StructureForeachFunc
noStructureForeachFunc_WithClosures :: Maybe StructureForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
StructureForeachFunc_WithClosures
wrap_StructureForeachFunc :: Maybe (Ptr (FunPtr C_StructureForeachFunc)) -> StructureForeachFunc_WithClosures -> C_StructureForeachFunc Source #
Wrap a StructureForeachFunc
into a C_StructureForeachFunc
.
StructureMapFunc
type C_StructureMapFunc = Word32 -> Ptr GValue -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type StructureMapFunc Source #
= Word32 |
|
-> GValue |
|
-> IO Bool | Returns: |
A function that will be called in structureMapInPlace
. The function
may modify value
.
type StructureMapFunc_WithClosures Source #
= Word32 |
|
-> GValue |
|
-> Ptr () |
|
-> IO Bool | Returns: |
A function that will be called in structureMapInPlace
. The function
may modify value
.
drop_closures_StructureMapFunc :: StructureMapFunc -> StructureMapFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_StructureMapFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_StructureMapFunc | |
-> Word32 |
|
-> GValue |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_StructureMapFunc :: MonadIO m => StructureMapFunc -> m (GClosure C_StructureMapFunc) Source #
Wrap the callback into a GClosure
.
mk_StructureMapFunc :: C_StructureMapFunc -> IO (FunPtr C_StructureMapFunc) Source #
Generate a function pointer callable from C code, from a C_StructureMapFunc
.
noStructureMapFunc :: Maybe StructureMapFunc Source #
A convenience synonym for
.Nothing
:: Maybe
StructureMapFunc
noStructureMapFunc_WithClosures :: Maybe StructureMapFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
StructureMapFunc_WithClosures
wrap_StructureMapFunc :: Maybe (Ptr (FunPtr C_StructureMapFunc)) -> StructureMapFunc_WithClosures -> C_StructureMapFunc Source #
Wrap a StructureMapFunc
into a C_StructureMapFunc
.
TagForeachFunc
type C_TagForeachFunc = Ptr TagList -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TagForeachFunc Source #
A function that will be called in tagListForeach
. The function may
not modify the tag list.
type TagForeachFunc_WithClosures Source #
= TagList |
|
-> Text |
|
-> Ptr () |
|
-> IO () |
A function that will be called in tagListForeach
. The function may
not modify the tag list.
drop_closures_TagForeachFunc :: TagForeachFunc -> TagForeachFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TagForeachFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_TagForeachFunc | |
-> TagList |
|
-> Text |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TagForeachFunc :: MonadIO m => TagForeachFunc -> m (GClosure C_TagForeachFunc) Source #
Wrap the callback into a GClosure
.
mk_TagForeachFunc :: C_TagForeachFunc -> IO (FunPtr C_TagForeachFunc) Source #
Generate a function pointer callable from C code, from a C_TagForeachFunc
.
noTagForeachFunc :: Maybe TagForeachFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TagForeachFunc
noTagForeachFunc_WithClosures :: Maybe TagForeachFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TagForeachFunc_WithClosures
wrap_TagForeachFunc :: Maybe (Ptr (FunPtr C_TagForeachFunc)) -> TagForeachFunc_WithClosures -> C_TagForeachFunc Source #
Wrap a TagForeachFunc
into a C_TagForeachFunc
.
TagMergeFunc
type C_TagMergeFunc = Ptr GValue -> Ptr GValue -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TagMergeFunc Source #
A function for merging multiple values of a tag used when registering tags.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_TagMergeFunc | |
-> GValue |
|
-> GValue |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TagMergeFunc :: MonadIO m => TagMergeFunc -> m (GClosure C_TagMergeFunc) Source #
Wrap the callback into a GClosure
.
mk_TagMergeFunc :: C_TagMergeFunc -> IO (FunPtr C_TagMergeFunc) Source #
Generate a function pointer callable from C code, from a C_TagMergeFunc
.
noTagMergeFunc :: Maybe TagMergeFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TagMergeFunc
wrap_TagMergeFunc :: Maybe (Ptr (FunPtr C_TagMergeFunc)) -> TagMergeFunc -> C_TagMergeFunc Source #
Wrap a TagMergeFunc
into a C_TagMergeFunc
.
TaskFunction
type C_TaskFunction = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TaskFunction = IO () Source #
A function that will repeatedly be called in the thread created by
a Task
.
type TaskFunction_WithClosures Source #
A function that will repeatedly be called in the thread created by
a Task
.
drop_closures_TaskFunction :: TaskFunction -> TaskFunction_WithClosures Source #
A simple wrapper that ignores the closure arguments.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_TaskFunction | |
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TaskFunction :: MonadIO m => TaskFunction -> m (GClosure C_TaskFunction) Source #
Wrap the callback into a GClosure
.
mk_TaskFunction :: C_TaskFunction -> IO (FunPtr C_TaskFunction) Source #
Generate a function pointer callable from C code, from a C_TaskFunction
.
noTaskFunction :: Maybe TaskFunction Source #
A convenience synonym for
.Nothing
:: Maybe
TaskFunction
noTaskFunction_WithClosures :: Maybe TaskFunction_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TaskFunction_WithClosures
wrap_TaskFunction :: Maybe (Ptr (FunPtr C_TaskFunction)) -> TaskFunction_WithClosures -> C_TaskFunction Source #
Wrap a TaskFunction
into a C_TaskFunction
.
TaskPoolFunction
type C_TaskPoolFunction = Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TaskPoolFunction = IO () Source #
Task function, see taskPoolPush
.
type TaskPoolFunction_WithClosures Source #
Task function, see taskPoolPush
.
drop_closures_TaskPoolFunction :: TaskPoolFunction -> TaskPoolFunction_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TaskPoolFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_TaskPoolFunction | |
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TaskPoolFunction :: MonadIO m => TaskPoolFunction -> m (GClosure C_TaskPoolFunction) Source #
Wrap the callback into a GClosure
.
mk_TaskPoolFunction :: C_TaskPoolFunction -> IO (FunPtr C_TaskPoolFunction) Source #
Generate a function pointer callable from C code, from a C_TaskPoolFunction
.
noTaskPoolFunction :: Maybe TaskPoolFunction Source #
A convenience synonym for
.Nothing
:: Maybe
TaskPoolFunction
noTaskPoolFunction_WithClosures :: Maybe TaskPoolFunction_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TaskPoolFunction_WithClosures
wrap_TaskPoolFunction :: Maybe (Ptr (FunPtr C_TaskPoolFunction)) -> TaskPoolFunction_WithClosures -> C_TaskPoolFunction Source #
Wrap a TaskPoolFunction
into a C_TaskPoolFunction
.
TaskThreadFunc
type C_TaskThreadFunc = Ptr Task -> Ptr Thread -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TaskThreadFunc Source #
Custom GstTask thread callback functions that can be installed.
type TaskThreadFunc_WithClosures Source #
Custom GstTask thread callback functions that can be installed.
drop_closures_TaskThreadFunc :: TaskThreadFunc -> TaskThreadFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TaskThreadFunc Source #
:: (HasCallStack, MonadIO m, IsTask a) | |
=> FunPtr C_TaskThreadFunc | |
-> a |
|
-> Thread |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TaskThreadFunc :: MonadIO m => TaskThreadFunc -> m (GClosure C_TaskThreadFunc) Source #
Wrap the callback into a GClosure
.
mk_TaskThreadFunc :: C_TaskThreadFunc -> IO (FunPtr C_TaskThreadFunc) Source #
Generate a function pointer callable from C code, from a C_TaskThreadFunc
.
noTaskThreadFunc :: Maybe TaskThreadFunc Source #
A convenience synonym for
.Nothing
:: Maybe
TaskThreadFunc
noTaskThreadFunc_WithClosures :: Maybe TaskThreadFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TaskThreadFunc_WithClosures
wrap_TaskThreadFunc :: Maybe (Ptr (FunPtr C_TaskThreadFunc)) -> TaskThreadFunc_WithClosures -> C_TaskThreadFunc Source #
Wrap a TaskThreadFunc
into a C_TaskThreadFunc
.
TypeFindFunction
type C_TypeFindFunction = Ptr TypeFind -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TypeFindFunction Source #
A function that will be called by typefinding.
type TypeFindFunction_WithClosures Source #
= TypeFind |
|
-> Ptr () |
|
-> IO () |
A function that will be called by typefinding.
drop_closures_TypeFindFunction :: TypeFindFunction -> TypeFindFunction_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_TypeFindFunction Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_TypeFindFunction | |
-> TypeFind |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TypeFindFunction :: MonadIO m => TypeFindFunction -> m (GClosure C_TypeFindFunction) Source #
Wrap the callback into a GClosure
.
mk_TypeFindFunction :: C_TypeFindFunction -> IO (FunPtr C_TypeFindFunction) Source #
Generate a function pointer callable from C code, from a C_TypeFindFunction
.
noTypeFindFunction :: Maybe TypeFindFunction Source #
A convenience synonym for
.Nothing
:: Maybe
TypeFindFunction
noTypeFindFunction_WithClosures :: Maybe TypeFindFunction_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
TypeFindFunction_WithClosures
wrap_TypeFindFunction :: Maybe (Ptr (FunPtr C_TypeFindFunction)) -> TypeFindFunction_WithClosures -> C_TypeFindFunction Source #
Wrap a TypeFindFunction
into a C_TypeFindFunction
.
TypeFindGetLengthFieldCallback
type C_TypeFindGetLengthFieldCallback = Ptr () -> IO Word64 Source #
Type for the callback on the (unwrapped) C side.
type TypeFindGetLengthFieldCallback = Ptr () -> IO Word64 Source #
No description available in the introspection data.
dynamic_TypeFindGetLengthFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_TypeFindGetLengthFieldCallback -> Ptr () -> m Word64 Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TypeFindGetLengthFieldCallback :: MonadIO m => TypeFindGetLengthFieldCallback -> m (GClosure C_TypeFindGetLengthFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_TypeFindGetLengthFieldCallback :: C_TypeFindGetLengthFieldCallback -> IO (FunPtr C_TypeFindGetLengthFieldCallback) Source #
Generate a function pointer callable from C code, from a C_TypeFindGetLengthFieldCallback
.
noTypeFindGetLengthFieldCallback :: Maybe TypeFindGetLengthFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TypeFindGetLengthFieldCallback
wrap_TypeFindGetLengthFieldCallback :: Maybe (Ptr (FunPtr C_TypeFindGetLengthFieldCallback)) -> TypeFindGetLengthFieldCallback -> C_TypeFindGetLengthFieldCallback Source #
Wrap a TypeFindGetLengthFieldCallback
into a C_TypeFindGetLengthFieldCallback
.
TypeFindPeekFieldCallback
type C_TypeFindPeekFieldCallback = Ptr () -> Int64 -> Word32 -> IO Word8 Source #
Type for the callback on the (unwrapped) C side.
type TypeFindPeekFieldCallback = Ptr () -> Int64 -> Word32 -> IO Word8 Source #
No description available in the introspection data.
dynamic_TypeFindPeekFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_TypeFindPeekFieldCallback -> Ptr () -> Int64 -> Word32 -> m Word8 Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TypeFindPeekFieldCallback :: MonadIO m => TypeFindPeekFieldCallback -> m (GClosure C_TypeFindPeekFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_TypeFindPeekFieldCallback :: C_TypeFindPeekFieldCallback -> IO (FunPtr C_TypeFindPeekFieldCallback) Source #
Generate a function pointer callable from C code, from a C_TypeFindPeekFieldCallback
.
noTypeFindPeekFieldCallback :: Maybe TypeFindPeekFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TypeFindPeekFieldCallback
wrap_TypeFindPeekFieldCallback :: Maybe (Ptr (FunPtr C_TypeFindPeekFieldCallback)) -> TypeFindPeekFieldCallback -> C_TypeFindPeekFieldCallback Source #
Wrap a TypeFindPeekFieldCallback
into a C_TypeFindPeekFieldCallback
.
TypeFindSuggestFieldCallback
type C_TypeFindSuggestFieldCallback = Ptr () -> Word32 -> Ptr Caps -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TypeFindSuggestFieldCallback = Ptr () -> Word32 -> Caps -> IO () Source #
No description available in the introspection data.
dynamic_TypeFindSuggestFieldCallback :: (HasCallStack, MonadIO m) => FunPtr C_TypeFindSuggestFieldCallback -> Ptr () -> Word32 -> Caps -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TypeFindSuggestFieldCallback :: MonadIO m => TypeFindSuggestFieldCallback -> m (GClosure C_TypeFindSuggestFieldCallback) Source #
Wrap the callback into a GClosure
.
mk_TypeFindSuggestFieldCallback :: C_TypeFindSuggestFieldCallback -> IO (FunPtr C_TypeFindSuggestFieldCallback) Source #
Generate a function pointer callable from C code, from a C_TypeFindSuggestFieldCallback
.
noTypeFindSuggestFieldCallback :: Maybe TypeFindSuggestFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
TypeFindSuggestFieldCallback
wrap_TypeFindSuggestFieldCallback :: Maybe (Ptr (FunPtr C_TypeFindSuggestFieldCallback)) -> TypeFindSuggestFieldCallback -> C_TypeFindSuggestFieldCallback Source #
Wrap a TypeFindSuggestFieldCallback
into a C_TypeFindSuggestFieldCallback
.
ValueCompareFunc
type C_ValueCompareFunc = Ptr GValue -> Ptr GValue -> IO Int32 Source #
Type for the callback on the (unwrapped) C side.
type ValueCompareFunc Source #
= GValue |
|
-> GValue |
|
-> IO Int32 | Returns: one of GST_VALUE_LESS_THAN, GST_VALUE_EQUAL, GST_VALUE_GREATER_THAN or GST_VALUE_UNORDERED |
Used together with valueCompare
to compare Value
items.
dynamic_ValueCompareFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_ValueCompareFunc | |
-> GValue |
|
-> GValue |
|
-> m Int32 | Returns: one of GST_VALUE_LESS_THAN, GST_VALUE_EQUAL, GST_VALUE_GREATER_THAN or GST_VALUE_UNORDERED |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ValueCompareFunc :: MonadIO m => ValueCompareFunc -> m (GClosure C_ValueCompareFunc) Source #
Wrap the callback into a GClosure
.
mk_ValueCompareFunc :: C_ValueCompareFunc -> IO (FunPtr C_ValueCompareFunc) Source #
Generate a function pointer callable from C code, from a C_ValueCompareFunc
.
noValueCompareFunc :: Maybe ValueCompareFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ValueCompareFunc
wrap_ValueCompareFunc :: Maybe (Ptr (FunPtr C_ValueCompareFunc)) -> ValueCompareFunc -> C_ValueCompareFunc Source #
Wrap a ValueCompareFunc
into a C_ValueCompareFunc
.
ValueDeserializeFunc
type C_ValueDeserializeFunc = Ptr GValue -> CString -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type ValueDeserializeFunc Source #
Used by valueDeserialize
to parse a non-binary form into the Value
.
dynamic_ValueDeserializeFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_ValueDeserializeFunc | |
-> GValue |
|
-> Text |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ValueDeserializeFunc :: MonadIO m => ValueDeserializeFunc -> m (GClosure C_ValueDeserializeFunc) Source #
Wrap the callback into a GClosure
.
mk_ValueDeserializeFunc :: C_ValueDeserializeFunc -> IO (FunPtr C_ValueDeserializeFunc) Source #
Generate a function pointer callable from C code, from a C_ValueDeserializeFunc
.
noValueDeserializeFunc :: Maybe ValueDeserializeFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ValueDeserializeFunc
wrap_ValueDeserializeFunc :: Maybe (Ptr (FunPtr C_ValueDeserializeFunc)) -> ValueDeserializeFunc -> C_ValueDeserializeFunc Source #
Wrap a ValueDeserializeFunc
into a C_ValueDeserializeFunc
.
ValueSerializeFunc
type C_ValueSerializeFunc = Ptr GValue -> IO CString Source #
Type for the callback on the (unwrapped) C side.
type ValueSerializeFunc Source #
Used by valueSerialize
to obtain a non-binary form of the Value
.
Free-function: g_free
dynamic_ValueSerializeFunc Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_ValueSerializeFunc | |
-> GValue |
|
-> m Text | Returns: the string representation of the value |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ValueSerializeFunc :: MonadIO m => ValueSerializeFunc -> m (GClosure C_ValueSerializeFunc) Source #
Wrap the callback into a GClosure
.
mk_ValueSerializeFunc :: C_ValueSerializeFunc -> IO (FunPtr C_ValueSerializeFunc) Source #
Generate a function pointer callable from C code, from a C_ValueSerializeFunc
.
noValueSerializeFunc :: Maybe ValueSerializeFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ValueSerializeFunc
wrap_ValueSerializeFunc :: Maybe (Ptr (FunPtr C_ValueSerializeFunc)) -> ValueSerializeFunc -> C_ValueSerializeFunc Source #
Wrap a ValueSerializeFunc
into a C_ValueSerializeFunc
.