Copyright | Will Thompson Iñaki García Etxebarria and Jonas Platte |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria (garetxe@gmail.com) |
Safe Haskell | None |
Language | Haskell2010 |
- Signals
- ActionEntryActivateFieldCallback
- ActionEntryChangeStateFieldCallback
- AsyncReadyCallback
- BusAcquiredCallback
- BusNameAcquiredCallback
- BusNameAppearedCallback
- BusNameLostCallback
- BusNameVanishedCallback
- CancellableSourceFunc
- DBusInterfaceGetPropertyFunc
- DBusInterfaceMethodCallFunc
- DBusInterfaceSetPropertyFunc
- DBusMessageFilterFunction
- DBusProxyTypeFunc
- DBusSignalCallback
- DBusSubtreeDispatchFunc
- DBusSubtreeIntrospectFunc
- DatagramBasedSourceFunc
- DesktopAppLaunchCallback
- FileMeasureProgressCallback
- FileProgressCallback
- FileReadMoreCallback
- IOSchedulerJobFunc
- PollableSourceFunc
- ReallocFunc
- SettingsBindGetMapping
- SettingsBindSetMapping
- SettingsGetMapping
- SimpleAsyncThreadFunc
- SocketSourceFunc
- TaskThreadFunc
- VfsFileLookupFunc
Synopsis
- type ActionEntryActivateFieldCallback = SimpleAction -> Maybe GVariant -> IO ()
- type ActionEntryActivateFieldCallback_WithClosures = SimpleAction -> Maybe GVariant -> Ptr () -> IO ()
- type C_ActionEntryActivateFieldCallback = Ptr SimpleAction -> Ptr GVariant -> Ptr () -> IO ()
- drop_closures_ActionEntryActivateFieldCallback :: ActionEntryActivateFieldCallback -> ActionEntryActivateFieldCallback_WithClosures
- dynamic_ActionEntryActivateFieldCallback :: (HasCallStack, MonadIO m, IsSimpleAction a) => FunPtr C_ActionEntryActivateFieldCallback -> a -> Maybe GVariant -> Ptr () -> m ()
- genClosure_ActionEntryActivateFieldCallback :: ActionEntryActivateFieldCallback -> IO Closure
- mk_ActionEntryActivateFieldCallback :: C_ActionEntryActivateFieldCallback -> IO (FunPtr C_ActionEntryActivateFieldCallback)
- noActionEntryActivateFieldCallback :: Maybe ActionEntryActivateFieldCallback
- noActionEntryActivateFieldCallback_WithClosures :: Maybe ActionEntryActivateFieldCallback_WithClosures
- wrap_ActionEntryActivateFieldCallback :: Maybe (Ptr (FunPtr C_ActionEntryActivateFieldCallback)) -> ActionEntryActivateFieldCallback_WithClosures -> C_ActionEntryActivateFieldCallback
- type ActionEntryChangeStateFieldCallback = SimpleAction -> GVariant -> IO ()
- type ActionEntryChangeStateFieldCallback_WithClosures = SimpleAction -> GVariant -> Ptr () -> IO ()
- type C_ActionEntryChangeStateFieldCallback = Ptr SimpleAction -> Ptr GVariant -> Ptr () -> IO ()
- drop_closures_ActionEntryChangeStateFieldCallback :: ActionEntryChangeStateFieldCallback -> ActionEntryChangeStateFieldCallback_WithClosures
- dynamic_ActionEntryChangeStateFieldCallback :: (HasCallStack, MonadIO m, IsSimpleAction a) => FunPtr C_ActionEntryChangeStateFieldCallback -> a -> GVariant -> Ptr () -> m ()
- genClosure_ActionEntryChangeStateFieldCallback :: ActionEntryChangeStateFieldCallback -> IO Closure
- mk_ActionEntryChangeStateFieldCallback :: C_ActionEntryChangeStateFieldCallback -> IO (FunPtr C_ActionEntryChangeStateFieldCallback)
- noActionEntryChangeStateFieldCallback :: Maybe ActionEntryChangeStateFieldCallback
- noActionEntryChangeStateFieldCallback_WithClosures :: Maybe ActionEntryChangeStateFieldCallback_WithClosures
- wrap_ActionEntryChangeStateFieldCallback :: Maybe (Ptr (FunPtr C_ActionEntryChangeStateFieldCallback)) -> ActionEntryChangeStateFieldCallback_WithClosures -> C_ActionEntryChangeStateFieldCallback
- type AsyncReadyCallback = Maybe Object -> AsyncResult -> IO ()
- type AsyncReadyCallback_WithClosures = Maybe Object -> AsyncResult -> Ptr () -> IO ()
- type C_AsyncReadyCallback = Ptr Object -> Ptr AsyncResult -> Ptr () -> IO ()
- drop_closures_AsyncReadyCallback :: AsyncReadyCallback -> AsyncReadyCallback_WithClosures
- dynamic_AsyncReadyCallback :: (HasCallStack, MonadIO m, IsObject a, IsAsyncResult b) => FunPtr C_AsyncReadyCallback -> Maybe a -> b -> Ptr () -> m ()
- genClosure_AsyncReadyCallback :: AsyncReadyCallback -> IO Closure
- mk_AsyncReadyCallback :: C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
- noAsyncReadyCallback :: Maybe AsyncReadyCallback
- noAsyncReadyCallback_WithClosures :: Maybe AsyncReadyCallback_WithClosures
- wrap_AsyncReadyCallback :: Maybe (Ptr (FunPtr C_AsyncReadyCallback)) -> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
- type BusAcquiredCallback = DBusConnection -> Text -> IO ()
- type BusAcquiredCallback_WithClosures = DBusConnection -> Text -> Ptr () -> IO ()
- type C_BusAcquiredCallback = Ptr DBusConnection -> CString -> Ptr () -> IO ()
- drop_closures_BusAcquiredCallback :: BusAcquiredCallback -> BusAcquiredCallback_WithClosures
- dynamic_BusAcquiredCallback :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_BusAcquiredCallback -> a -> Text -> Ptr () -> m ()
- genClosure_BusAcquiredCallback :: BusAcquiredCallback -> IO Closure
- mk_BusAcquiredCallback :: C_BusAcquiredCallback -> IO (FunPtr C_BusAcquiredCallback)
- noBusAcquiredCallback :: Maybe BusAcquiredCallback
- noBusAcquiredCallback_WithClosures :: Maybe BusAcquiredCallback_WithClosures
- wrap_BusAcquiredCallback :: Maybe (Ptr (FunPtr C_BusAcquiredCallback)) -> BusAcquiredCallback_WithClosures -> C_BusAcquiredCallback
- type BusNameAcquiredCallback = DBusConnection -> Text -> IO ()
- type BusNameAcquiredCallback_WithClosures = DBusConnection -> Text -> Ptr () -> IO ()
- type C_BusNameAcquiredCallback = Ptr DBusConnection -> CString -> Ptr () -> IO ()
- drop_closures_BusNameAcquiredCallback :: BusNameAcquiredCallback -> BusNameAcquiredCallback_WithClosures
- dynamic_BusNameAcquiredCallback :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_BusNameAcquiredCallback -> a -> Text -> Ptr () -> m ()
- genClosure_BusNameAcquiredCallback :: BusNameAcquiredCallback -> IO Closure
- mk_BusNameAcquiredCallback :: C_BusNameAcquiredCallback -> IO (FunPtr C_BusNameAcquiredCallback)
- noBusNameAcquiredCallback :: Maybe BusNameAcquiredCallback
- noBusNameAcquiredCallback_WithClosures :: Maybe BusNameAcquiredCallback_WithClosures
- wrap_BusNameAcquiredCallback :: Maybe (Ptr (FunPtr C_BusNameAcquiredCallback)) -> BusNameAcquiredCallback_WithClosures -> C_BusNameAcquiredCallback
- type BusNameAppearedCallback = DBusConnection -> Text -> Text -> IO ()
- type BusNameAppearedCallback_WithClosures = DBusConnection -> Text -> Text -> Ptr () -> IO ()
- type C_BusNameAppearedCallback = Ptr DBusConnection -> CString -> CString -> Ptr () -> IO ()
- drop_closures_BusNameAppearedCallback :: BusNameAppearedCallback -> BusNameAppearedCallback_WithClosures
- dynamic_BusNameAppearedCallback :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_BusNameAppearedCallback -> a -> Text -> Text -> Ptr () -> m ()
- genClosure_BusNameAppearedCallback :: BusNameAppearedCallback -> IO Closure
- mk_BusNameAppearedCallback :: C_BusNameAppearedCallback -> IO (FunPtr C_BusNameAppearedCallback)
- noBusNameAppearedCallback :: Maybe BusNameAppearedCallback
- noBusNameAppearedCallback_WithClosures :: Maybe BusNameAppearedCallback_WithClosures
- wrap_BusNameAppearedCallback :: Maybe (Ptr (FunPtr C_BusNameAppearedCallback)) -> BusNameAppearedCallback_WithClosures -> C_BusNameAppearedCallback
- type BusNameLostCallback = DBusConnection -> Text -> IO ()
- type BusNameLostCallback_WithClosures = DBusConnection -> Text -> Ptr () -> IO ()
- type C_BusNameLostCallback = Ptr DBusConnection -> CString -> Ptr () -> IO ()
- drop_closures_BusNameLostCallback :: BusNameLostCallback -> BusNameLostCallback_WithClosures
- dynamic_BusNameLostCallback :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_BusNameLostCallback -> a -> Text -> Ptr () -> m ()
- genClosure_BusNameLostCallback :: BusNameLostCallback -> IO Closure
- mk_BusNameLostCallback :: C_BusNameLostCallback -> IO (FunPtr C_BusNameLostCallback)
- noBusNameLostCallback :: Maybe BusNameLostCallback
- noBusNameLostCallback_WithClosures :: Maybe BusNameLostCallback_WithClosures
- wrap_BusNameLostCallback :: Maybe (Ptr (FunPtr C_BusNameLostCallback)) -> BusNameLostCallback_WithClosures -> C_BusNameLostCallback
- type BusNameVanishedCallback = DBusConnection -> Text -> IO ()
- type BusNameVanishedCallback_WithClosures = DBusConnection -> Text -> Ptr () -> IO ()
- type C_BusNameVanishedCallback = Ptr DBusConnection -> CString -> Ptr () -> IO ()
- drop_closures_BusNameVanishedCallback :: BusNameVanishedCallback -> BusNameVanishedCallback_WithClosures
- dynamic_BusNameVanishedCallback :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_BusNameVanishedCallback -> a -> Text -> Ptr () -> m ()
- genClosure_BusNameVanishedCallback :: BusNameVanishedCallback -> IO Closure
- mk_BusNameVanishedCallback :: C_BusNameVanishedCallback -> IO (FunPtr C_BusNameVanishedCallback)
- noBusNameVanishedCallback :: Maybe BusNameVanishedCallback
- noBusNameVanishedCallback_WithClosures :: Maybe BusNameVanishedCallback_WithClosures
- wrap_BusNameVanishedCallback :: Maybe (Ptr (FunPtr C_BusNameVanishedCallback)) -> BusNameVanishedCallback_WithClosures -> C_BusNameVanishedCallback
- type C_CancellableSourceFunc = Ptr Cancellable -> Ptr () -> IO CInt
- type CancellableSourceFunc = Maybe Cancellable -> IO Bool
- type CancellableSourceFunc_WithClosures = Maybe Cancellable -> Ptr () -> IO Bool
- drop_closures_CancellableSourceFunc :: CancellableSourceFunc -> CancellableSourceFunc_WithClosures
- dynamic_CancellableSourceFunc :: (HasCallStack, MonadIO m, IsCancellable a) => FunPtr C_CancellableSourceFunc -> Maybe a -> Ptr () -> m Bool
- genClosure_CancellableSourceFunc :: CancellableSourceFunc -> IO Closure
- mk_CancellableSourceFunc :: C_CancellableSourceFunc -> IO (FunPtr C_CancellableSourceFunc)
- noCancellableSourceFunc :: Maybe CancellableSourceFunc
- noCancellableSourceFunc_WithClosures :: Maybe CancellableSourceFunc_WithClosures
- wrap_CancellableSourceFunc :: Maybe (Ptr (FunPtr C_CancellableSourceFunc)) -> CancellableSourceFunc_WithClosures -> C_CancellableSourceFunc
- type C_DBusInterfaceGetPropertyFunc = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr GError -> Ptr () -> IO (Ptr GVariant)
- type DBusInterfaceGetPropertyFunc = DBusConnection -> Text -> Text -> Text -> Text -> GError -> IO GVariant
- type DBusInterfaceGetPropertyFunc_WithClosures = DBusConnection -> Text -> Text -> Text -> Text -> GError -> Ptr () -> IO GVariant
- drop_closures_DBusInterfaceGetPropertyFunc :: DBusInterfaceGetPropertyFunc -> DBusInterfaceGetPropertyFunc_WithClosures
- dynamic_DBusInterfaceGetPropertyFunc :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_DBusInterfaceGetPropertyFunc -> a -> Text -> Text -> Text -> Text -> GError -> Ptr () -> m GVariant
- genClosure_DBusInterfaceGetPropertyFunc :: DBusInterfaceGetPropertyFunc -> IO Closure
- mk_DBusInterfaceGetPropertyFunc :: C_DBusInterfaceGetPropertyFunc -> IO (FunPtr C_DBusInterfaceGetPropertyFunc)
- noDBusInterfaceGetPropertyFunc :: Maybe DBusInterfaceGetPropertyFunc
- noDBusInterfaceGetPropertyFunc_WithClosures :: Maybe DBusInterfaceGetPropertyFunc_WithClosures
- wrap_DBusInterfaceGetPropertyFunc :: Maybe (Ptr (FunPtr C_DBusInterfaceGetPropertyFunc)) -> DBusInterfaceGetPropertyFunc_WithClosures -> C_DBusInterfaceGetPropertyFunc
- type C_DBusInterfaceMethodCallFunc = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr GVariant -> Ptr DBusMethodInvocation -> Ptr () -> IO ()
- type DBusInterfaceMethodCallFunc = DBusConnection -> Text -> Text -> Text -> Text -> GVariant -> DBusMethodInvocation -> IO ()
- type DBusInterfaceMethodCallFunc_WithClosures = DBusConnection -> Text -> Text -> Text -> Text -> GVariant -> DBusMethodInvocation -> Ptr () -> IO ()
- drop_closures_DBusInterfaceMethodCallFunc :: DBusInterfaceMethodCallFunc -> DBusInterfaceMethodCallFunc_WithClosures
- dynamic_DBusInterfaceMethodCallFunc :: (HasCallStack, MonadIO m, IsDBusConnection a, IsDBusMethodInvocation b) => FunPtr C_DBusInterfaceMethodCallFunc -> a -> Text -> Text -> Text -> Text -> GVariant -> b -> Ptr () -> m ()
- genClosure_DBusInterfaceMethodCallFunc :: DBusInterfaceMethodCallFunc -> IO Closure
- mk_DBusInterfaceMethodCallFunc :: C_DBusInterfaceMethodCallFunc -> IO (FunPtr C_DBusInterfaceMethodCallFunc)
- noDBusInterfaceMethodCallFunc :: Maybe DBusInterfaceMethodCallFunc
- noDBusInterfaceMethodCallFunc_WithClosures :: Maybe DBusInterfaceMethodCallFunc_WithClosures
- wrap_DBusInterfaceMethodCallFunc :: Maybe (Ptr (FunPtr C_DBusInterfaceMethodCallFunc)) -> DBusInterfaceMethodCallFunc_WithClosures -> C_DBusInterfaceMethodCallFunc
- type C_DBusInterfaceSetPropertyFunc = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr GVariant -> Ptr GError -> Ptr () -> IO CInt
- type DBusInterfaceSetPropertyFunc = DBusConnection -> Text -> Text -> Text -> Text -> GVariant -> GError -> IO Bool
- type DBusInterfaceSetPropertyFunc_WithClosures = DBusConnection -> Text -> Text -> Text -> Text -> GVariant -> GError -> Ptr () -> IO Bool
- drop_closures_DBusInterfaceSetPropertyFunc :: DBusInterfaceSetPropertyFunc -> DBusInterfaceSetPropertyFunc_WithClosures
- dynamic_DBusInterfaceSetPropertyFunc :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_DBusInterfaceSetPropertyFunc -> a -> Text -> Text -> Text -> Text -> GVariant -> GError -> Ptr () -> m Bool
- genClosure_DBusInterfaceSetPropertyFunc :: DBusInterfaceSetPropertyFunc -> IO Closure
- mk_DBusInterfaceSetPropertyFunc :: C_DBusInterfaceSetPropertyFunc -> IO (FunPtr C_DBusInterfaceSetPropertyFunc)
- noDBusInterfaceSetPropertyFunc :: Maybe DBusInterfaceSetPropertyFunc
- noDBusInterfaceSetPropertyFunc_WithClosures :: Maybe DBusInterfaceSetPropertyFunc_WithClosures
- wrap_DBusInterfaceSetPropertyFunc :: Maybe (Ptr (FunPtr C_DBusInterfaceSetPropertyFunc)) -> DBusInterfaceSetPropertyFunc_WithClosures -> C_DBusInterfaceSetPropertyFunc
- type C_DBusMessageFilterFunction = Ptr DBusConnection -> Ptr DBusMessage -> CInt -> Ptr () -> IO (Ptr DBusMessage)
- type DBusMessageFilterFunction = DBusConnection -> DBusMessage -> Bool -> IO (Maybe DBusMessage)
- type DBusMessageFilterFunction_WithClosures = DBusConnection -> DBusMessage -> Bool -> Ptr () -> IO (Maybe DBusMessage)
- drop_closures_DBusMessageFilterFunction :: DBusMessageFilterFunction -> DBusMessageFilterFunction_WithClosures
- dynamic_DBusMessageFilterFunction :: (HasCallStack, MonadIO m, IsDBusConnection a, IsDBusMessage b) => FunPtr C_DBusMessageFilterFunction -> a -> b -> Bool -> Ptr () -> m (Maybe DBusMessage)
- genClosure_DBusMessageFilterFunction :: DBusMessageFilterFunction -> IO Closure
- mk_DBusMessageFilterFunction :: C_DBusMessageFilterFunction -> IO (FunPtr C_DBusMessageFilterFunction)
- noDBusMessageFilterFunction :: Maybe DBusMessageFilterFunction
- noDBusMessageFilterFunction_WithClosures :: Maybe DBusMessageFilterFunction_WithClosures
- wrap_DBusMessageFilterFunction :: Maybe (Ptr (FunPtr C_DBusMessageFilterFunction)) -> DBusMessageFilterFunction_WithClosures -> C_DBusMessageFilterFunction
- type C_DBusProxyTypeFunc = Ptr DBusObjectManagerClient -> CString -> CString -> Ptr () -> IO CGType
- type DBusProxyTypeFunc = DBusObjectManagerClient -> Text -> Maybe Text -> IO GType
- type DBusProxyTypeFunc_WithClosures = DBusObjectManagerClient -> Text -> Maybe Text -> Ptr () -> IO GType
- drop_closures_DBusProxyTypeFunc :: DBusProxyTypeFunc -> DBusProxyTypeFunc_WithClosures
- dynamic_DBusProxyTypeFunc :: (HasCallStack, MonadIO m, IsDBusObjectManagerClient a) => FunPtr C_DBusProxyTypeFunc -> a -> Text -> Maybe Text -> Ptr () -> m GType
- genClosure_DBusProxyTypeFunc :: DBusProxyTypeFunc -> IO Closure
- mk_DBusProxyTypeFunc :: C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc)
- noDBusProxyTypeFunc :: Maybe DBusProxyTypeFunc
- noDBusProxyTypeFunc_WithClosures :: Maybe DBusProxyTypeFunc_WithClosures
- wrap_DBusProxyTypeFunc :: Maybe (Ptr (FunPtr C_DBusProxyTypeFunc)) -> DBusProxyTypeFunc_WithClosures -> C_DBusProxyTypeFunc
- type C_DBusSignalCallback = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr GVariant -> Ptr () -> IO ()
- type DBusSignalCallback = DBusConnection -> Text -> Text -> Text -> Text -> GVariant -> IO ()
- type DBusSignalCallback_WithClosures = DBusConnection -> Text -> Text -> Text -> Text -> GVariant -> Ptr () -> IO ()
- drop_closures_DBusSignalCallback :: DBusSignalCallback -> DBusSignalCallback_WithClosures
- dynamic_DBusSignalCallback :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_DBusSignalCallback -> a -> Text -> Text -> Text -> Text -> GVariant -> Ptr () -> m ()
- genClosure_DBusSignalCallback :: DBusSignalCallback -> IO Closure
- mk_DBusSignalCallback :: C_DBusSignalCallback -> IO (FunPtr C_DBusSignalCallback)
- noDBusSignalCallback :: Maybe DBusSignalCallback
- noDBusSignalCallback_WithClosures :: Maybe DBusSignalCallback_WithClosures
- wrap_DBusSignalCallback :: Maybe (Ptr (FunPtr C_DBusSignalCallback)) -> DBusSignalCallback_WithClosures -> C_DBusSignalCallback
- type C_DBusSubtreeDispatchFunc = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr () -> Ptr () -> IO (Ptr DBusInterfaceVTable)
- type DBusSubtreeDispatchFunc = DBusConnection -> Text -> Text -> Text -> Text -> Ptr () -> IO DBusInterfaceVTable
- type DBusSubtreeDispatchFunc_WithClosures = DBusConnection -> Text -> Text -> Text -> Text -> Ptr () -> Ptr () -> IO DBusInterfaceVTable
- drop_closures_DBusSubtreeDispatchFunc :: DBusSubtreeDispatchFunc -> DBusSubtreeDispatchFunc_WithClosures
- dynamic_DBusSubtreeDispatchFunc :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_DBusSubtreeDispatchFunc -> a -> Text -> Text -> Text -> Text -> Ptr () -> Ptr () -> m DBusInterfaceVTable
- genClosure_DBusSubtreeDispatchFunc :: DBusSubtreeDispatchFunc -> IO Closure
- mk_DBusSubtreeDispatchFunc :: C_DBusSubtreeDispatchFunc -> IO (FunPtr C_DBusSubtreeDispatchFunc)
- noDBusSubtreeDispatchFunc :: Maybe DBusSubtreeDispatchFunc
- noDBusSubtreeDispatchFunc_WithClosures :: Maybe DBusSubtreeDispatchFunc_WithClosures
- wrap_DBusSubtreeDispatchFunc :: Maybe (Ptr (FunPtr C_DBusSubtreeDispatchFunc)) -> DBusSubtreeDispatchFunc_WithClosures -> C_DBusSubtreeDispatchFunc
- type C_DBusSubtreeIntrospectFunc = Ptr DBusConnection -> CString -> CString -> CString -> Ptr () -> IO (Ptr DBusInterfaceInfo)
- type DBusSubtreeIntrospectFunc = DBusConnection -> Text -> Text -> Text -> IO DBusInterfaceInfo
- type DBusSubtreeIntrospectFunc_WithClosures = DBusConnection -> Text -> Text -> Text -> Ptr () -> IO DBusInterfaceInfo
- drop_closures_DBusSubtreeIntrospectFunc :: DBusSubtreeIntrospectFunc -> DBusSubtreeIntrospectFunc_WithClosures
- dynamic_DBusSubtreeIntrospectFunc :: (HasCallStack, MonadIO m, IsDBusConnection a) => FunPtr C_DBusSubtreeIntrospectFunc -> a -> Text -> Text -> Text -> Ptr () -> m DBusInterfaceInfo
- genClosure_DBusSubtreeIntrospectFunc :: DBusSubtreeIntrospectFunc -> IO Closure
- mk_DBusSubtreeIntrospectFunc :: C_DBusSubtreeIntrospectFunc -> IO (FunPtr C_DBusSubtreeIntrospectFunc)
- noDBusSubtreeIntrospectFunc :: Maybe DBusSubtreeIntrospectFunc
- noDBusSubtreeIntrospectFunc_WithClosures :: Maybe DBusSubtreeIntrospectFunc_WithClosures
- wrap_DBusSubtreeIntrospectFunc :: Maybe (Ptr (FunPtr C_DBusSubtreeIntrospectFunc)) -> DBusSubtreeIntrospectFunc_WithClosures -> C_DBusSubtreeIntrospectFunc
- type C_DatagramBasedSourceFunc = Ptr DatagramBased -> CUInt -> Ptr () -> IO CInt
- type DatagramBasedSourceFunc = DatagramBased -> [IOCondition] -> IO Bool
- type DatagramBasedSourceFunc_WithClosures = DatagramBased -> [IOCondition] -> Ptr () -> IO Bool
- drop_closures_DatagramBasedSourceFunc :: DatagramBasedSourceFunc -> DatagramBasedSourceFunc_WithClosures
- dynamic_DatagramBasedSourceFunc :: (HasCallStack, MonadIO m, IsDatagramBased a) => FunPtr C_DatagramBasedSourceFunc -> a -> [IOCondition] -> Ptr () -> m Bool
- genClosure_DatagramBasedSourceFunc :: DatagramBasedSourceFunc -> IO Closure
- mk_DatagramBasedSourceFunc :: C_DatagramBasedSourceFunc -> IO (FunPtr C_DatagramBasedSourceFunc)
- noDatagramBasedSourceFunc :: Maybe DatagramBasedSourceFunc
- noDatagramBasedSourceFunc_WithClosures :: Maybe DatagramBasedSourceFunc_WithClosures
- wrap_DatagramBasedSourceFunc :: Maybe (Ptr (FunPtr C_DatagramBasedSourceFunc)) -> DatagramBasedSourceFunc_WithClosures -> C_DatagramBasedSourceFunc
- type C_DesktopAppLaunchCallback = Ptr DesktopAppInfo -> Int32 -> Ptr () -> IO ()
- type DesktopAppLaunchCallback = DesktopAppInfo -> Int32 -> IO ()
- type DesktopAppLaunchCallback_WithClosures = DesktopAppInfo -> Int32 -> Ptr () -> IO ()
- drop_closures_DesktopAppLaunchCallback :: DesktopAppLaunchCallback -> DesktopAppLaunchCallback_WithClosures
- dynamic_DesktopAppLaunchCallback :: (HasCallStack, MonadIO m, IsDesktopAppInfo a) => FunPtr C_DesktopAppLaunchCallback -> a -> Int32 -> Ptr () -> m ()
- genClosure_DesktopAppLaunchCallback :: DesktopAppLaunchCallback -> IO Closure
- mk_DesktopAppLaunchCallback :: C_DesktopAppLaunchCallback -> IO (FunPtr C_DesktopAppLaunchCallback)
- noDesktopAppLaunchCallback :: Maybe DesktopAppLaunchCallback
- noDesktopAppLaunchCallback_WithClosures :: Maybe DesktopAppLaunchCallback_WithClosures
- wrap_DesktopAppLaunchCallback :: Maybe (Ptr (FunPtr C_DesktopAppLaunchCallback)) -> DesktopAppLaunchCallback_WithClosures -> C_DesktopAppLaunchCallback
- type C_FileMeasureProgressCallback = CInt -> Word64 -> Word64 -> Word64 -> Ptr () -> IO ()
- type FileMeasureProgressCallback = Bool -> Word64 -> Word64 -> Word64 -> IO ()
- type FileMeasureProgressCallback_WithClosures = Bool -> Word64 -> Word64 -> Word64 -> Ptr () -> IO ()
- drop_closures_FileMeasureProgressCallback :: FileMeasureProgressCallback -> FileMeasureProgressCallback_WithClosures
- dynamic_FileMeasureProgressCallback :: (HasCallStack, MonadIO m) => FunPtr C_FileMeasureProgressCallback -> Bool -> Word64 -> Word64 -> Word64 -> Ptr () -> m ()
- genClosure_FileMeasureProgressCallback :: FileMeasureProgressCallback -> IO Closure
- mk_FileMeasureProgressCallback :: C_FileMeasureProgressCallback -> IO (FunPtr C_FileMeasureProgressCallback)
- noFileMeasureProgressCallback :: Maybe FileMeasureProgressCallback
- noFileMeasureProgressCallback_WithClosures :: Maybe FileMeasureProgressCallback_WithClosures
- wrap_FileMeasureProgressCallback :: Maybe (Ptr (FunPtr C_FileMeasureProgressCallback)) -> FileMeasureProgressCallback_WithClosures -> C_FileMeasureProgressCallback
- type C_FileProgressCallback = Int64 -> Int64 -> Ptr () -> IO ()
- type FileProgressCallback = Int64 -> Int64 -> IO ()
- type FileProgressCallback_WithClosures = Int64 -> Int64 -> Ptr () -> IO ()
- drop_closures_FileProgressCallback :: FileProgressCallback -> FileProgressCallback_WithClosures
- dynamic_FileProgressCallback :: (HasCallStack, MonadIO m) => FunPtr C_FileProgressCallback -> Int64 -> Int64 -> Ptr () -> m ()
- genClosure_FileProgressCallback :: FileProgressCallback -> IO Closure
- mk_FileProgressCallback :: C_FileProgressCallback -> IO (FunPtr C_FileProgressCallback)
- noFileProgressCallback :: Maybe FileProgressCallback
- noFileProgressCallback_WithClosures :: Maybe FileProgressCallback_WithClosures
- wrap_FileProgressCallback :: Maybe (Ptr (FunPtr C_FileProgressCallback)) -> FileProgressCallback_WithClosures -> C_FileProgressCallback
- type C_FileReadMoreCallback = CString -> Int64 -> Ptr () -> IO CInt
- type FileReadMoreCallback = Text -> Int64 -> IO Bool
- type FileReadMoreCallback_WithClosures = Text -> Int64 -> Ptr () -> IO Bool
- drop_closures_FileReadMoreCallback :: FileReadMoreCallback -> FileReadMoreCallback_WithClosures
- dynamic_FileReadMoreCallback :: (HasCallStack, MonadIO m) => FunPtr C_FileReadMoreCallback -> Text -> Int64 -> Ptr () -> m Bool
- genClosure_FileReadMoreCallback :: FileReadMoreCallback -> IO Closure
- mk_FileReadMoreCallback :: C_FileReadMoreCallback -> IO (FunPtr C_FileReadMoreCallback)
- noFileReadMoreCallback :: Maybe FileReadMoreCallback
- noFileReadMoreCallback_WithClosures :: Maybe FileReadMoreCallback_WithClosures
- wrap_FileReadMoreCallback :: Maybe (Ptr (FunPtr C_FileReadMoreCallback)) -> FileReadMoreCallback_WithClosures -> C_FileReadMoreCallback
- type C_IOSchedulerJobFunc = Ptr IOSchedulerJob -> Ptr Cancellable -> Ptr () -> IO CInt
- type IOSchedulerJobFunc = IOSchedulerJob -> Maybe Cancellable -> IO Bool
- type IOSchedulerJobFunc_WithClosures = IOSchedulerJob -> Maybe Cancellable -> Ptr () -> IO Bool
- drop_closures_IOSchedulerJobFunc :: IOSchedulerJobFunc -> IOSchedulerJobFunc_WithClosures
- dynamic_IOSchedulerJobFunc :: (HasCallStack, MonadIO m, IsCancellable a) => FunPtr C_IOSchedulerJobFunc -> IOSchedulerJob -> Maybe a -> Ptr () -> m Bool
- genClosure_IOSchedulerJobFunc :: IOSchedulerJobFunc -> IO Closure
- mk_IOSchedulerJobFunc :: C_IOSchedulerJobFunc -> IO (FunPtr C_IOSchedulerJobFunc)
- noIOSchedulerJobFunc :: Maybe IOSchedulerJobFunc
- noIOSchedulerJobFunc_WithClosures :: Maybe IOSchedulerJobFunc_WithClosures
- wrap_IOSchedulerJobFunc :: Maybe (Ptr (FunPtr C_IOSchedulerJobFunc)) -> IOSchedulerJobFunc_WithClosures -> C_IOSchedulerJobFunc
- type C_PollableSourceFunc = Ptr Object -> Ptr () -> IO CInt
- type PollableSourceFunc = Object -> IO Bool
- type PollableSourceFunc_WithClosures = Object -> Ptr () -> IO Bool
- drop_closures_PollableSourceFunc :: PollableSourceFunc -> PollableSourceFunc_WithClosures
- dynamic_PollableSourceFunc :: (HasCallStack, MonadIO m, IsObject a) => FunPtr C_PollableSourceFunc -> a -> Ptr () -> m Bool
- genClosure_PollableSourceFunc :: PollableSourceFunc -> IO Closure
- mk_PollableSourceFunc :: C_PollableSourceFunc -> IO (FunPtr C_PollableSourceFunc)
- noPollableSourceFunc :: Maybe PollableSourceFunc
- noPollableSourceFunc_WithClosures :: Maybe PollableSourceFunc_WithClosures
- wrap_PollableSourceFunc :: Maybe (Ptr (FunPtr C_PollableSourceFunc)) -> PollableSourceFunc_WithClosures -> C_PollableSourceFunc
- type C_ReallocFunc = Ptr () -> Word64 -> IO (Ptr ())
- type ReallocFunc = Ptr () -> Word64 -> IO (Ptr ())
- dynamic_ReallocFunc :: (HasCallStack, MonadIO m) => FunPtr C_ReallocFunc -> Ptr () -> Word64 -> m (Ptr ())
- genClosure_ReallocFunc :: ReallocFunc -> IO Closure
- mk_ReallocFunc :: C_ReallocFunc -> IO (FunPtr C_ReallocFunc)
- noReallocFunc :: Maybe ReallocFunc
- wrap_ReallocFunc :: Maybe (Ptr (FunPtr C_ReallocFunc)) -> ReallocFunc -> C_ReallocFunc
- type C_SettingsBindGetMapping = Ptr GValue -> Ptr GVariant -> Ptr () -> IO CInt
- type SettingsBindGetMapping = GValue -> GVariant -> IO Bool
- type SettingsBindGetMapping_WithClosures = GValue -> GVariant -> Ptr () -> IO Bool
- drop_closures_SettingsBindGetMapping :: SettingsBindGetMapping -> SettingsBindGetMapping_WithClosures
- dynamic_SettingsBindGetMapping :: (HasCallStack, MonadIO m) => FunPtr C_SettingsBindGetMapping -> GValue -> GVariant -> Ptr () -> m Bool
- genClosure_SettingsBindGetMapping :: SettingsBindGetMapping -> IO Closure
- mk_SettingsBindGetMapping :: C_SettingsBindGetMapping -> IO (FunPtr C_SettingsBindGetMapping)
- noSettingsBindGetMapping :: Maybe SettingsBindGetMapping
- noSettingsBindGetMapping_WithClosures :: Maybe SettingsBindGetMapping_WithClosures
- wrap_SettingsBindGetMapping :: Maybe (Ptr (FunPtr C_SettingsBindGetMapping)) -> SettingsBindGetMapping_WithClosures -> C_SettingsBindGetMapping
- type C_SettingsBindSetMapping = Ptr GValue -> Ptr VariantType -> Ptr () -> IO (Ptr GVariant)
- type SettingsBindSetMapping = GValue -> VariantType -> IO GVariant
- type SettingsBindSetMapping_WithClosures = GValue -> VariantType -> Ptr () -> IO GVariant
- drop_closures_SettingsBindSetMapping :: SettingsBindSetMapping -> SettingsBindSetMapping_WithClosures
- dynamic_SettingsBindSetMapping :: (HasCallStack, MonadIO m) => FunPtr C_SettingsBindSetMapping -> GValue -> VariantType -> Ptr () -> m GVariant
- genClosure_SettingsBindSetMapping :: SettingsBindSetMapping -> IO Closure
- mk_SettingsBindSetMapping :: C_SettingsBindSetMapping -> IO (FunPtr C_SettingsBindSetMapping)
- noSettingsBindSetMapping :: Maybe SettingsBindSetMapping
- noSettingsBindSetMapping_WithClosures :: Maybe SettingsBindSetMapping_WithClosures
- wrap_SettingsBindSetMapping :: Maybe (Ptr (FunPtr C_SettingsBindSetMapping)) -> SettingsBindSetMapping_WithClosures -> C_SettingsBindSetMapping
- type C_SettingsGetMapping = Ptr GVariant -> Ptr (Ptr ()) -> Ptr () -> IO CInt
- type SettingsGetMapping = GVariant -> IO (Bool, Ptr ())
- type SettingsGetMapping_WithClosures = GVariant -> Ptr () -> IO (Bool, Ptr ())
- drop_closures_SettingsGetMapping :: SettingsGetMapping -> SettingsGetMapping_WithClosures
- dynamic_SettingsGetMapping :: (HasCallStack, MonadIO m) => FunPtr C_SettingsGetMapping -> GVariant -> Ptr () -> m (Bool, Ptr ())
- genClosure_SettingsGetMapping :: SettingsGetMapping -> IO Closure
- mk_SettingsGetMapping :: C_SettingsGetMapping -> IO (FunPtr C_SettingsGetMapping)
- noSettingsGetMapping :: Maybe SettingsGetMapping
- noSettingsGetMapping_WithClosures :: Maybe SettingsGetMapping_WithClosures
- wrap_SettingsGetMapping :: Maybe (Ptr (FunPtr C_SettingsGetMapping)) -> SettingsGetMapping_WithClosures -> C_SettingsGetMapping
- type C_SimpleAsyncThreadFunc = Ptr SimpleAsyncResult -> Ptr Object -> Ptr Cancellable -> IO ()
- type SimpleAsyncThreadFunc = SimpleAsyncResult -> Object -> Maybe Cancellable -> IO ()
- dynamic_SimpleAsyncThreadFunc :: (HasCallStack, MonadIO m, IsSimpleAsyncResult a, IsObject b, IsCancellable c) => FunPtr C_SimpleAsyncThreadFunc -> a -> b -> Maybe c -> m ()
- genClosure_SimpleAsyncThreadFunc :: SimpleAsyncThreadFunc -> IO Closure
- mk_SimpleAsyncThreadFunc :: C_SimpleAsyncThreadFunc -> IO (FunPtr C_SimpleAsyncThreadFunc)
- noSimpleAsyncThreadFunc :: Maybe SimpleAsyncThreadFunc
- wrap_SimpleAsyncThreadFunc :: Maybe (Ptr (FunPtr C_SimpleAsyncThreadFunc)) -> SimpleAsyncThreadFunc -> C_SimpleAsyncThreadFunc
- type C_SocketSourceFunc = Ptr Socket -> CUInt -> Ptr () -> IO CInt
- type SocketSourceFunc = Socket -> [IOCondition] -> IO Bool
- type SocketSourceFunc_WithClosures = Socket -> [IOCondition] -> Ptr () -> IO Bool
- drop_closures_SocketSourceFunc :: SocketSourceFunc -> SocketSourceFunc_WithClosures
- dynamic_SocketSourceFunc :: (HasCallStack, MonadIO m, IsSocket a) => FunPtr C_SocketSourceFunc -> a -> [IOCondition] -> Ptr () -> m Bool
- genClosure_SocketSourceFunc :: SocketSourceFunc -> IO Closure
- mk_SocketSourceFunc :: C_SocketSourceFunc -> IO (FunPtr C_SocketSourceFunc)
- noSocketSourceFunc :: Maybe SocketSourceFunc
- noSocketSourceFunc_WithClosures :: Maybe SocketSourceFunc_WithClosures
- wrap_SocketSourceFunc :: Maybe (Ptr (FunPtr C_SocketSourceFunc)) -> SocketSourceFunc_WithClosures -> C_SocketSourceFunc
- type C_TaskThreadFunc = Ptr Task -> Ptr Object -> Ptr () -> Ptr Cancellable -> IO ()
- type TaskThreadFunc = Task -> Object -> Ptr () -> Maybe Cancellable -> IO ()
- dynamic_TaskThreadFunc :: (HasCallStack, MonadIO m, IsTask a, IsObject b, IsCancellable c) => FunPtr C_TaskThreadFunc -> a -> b -> Ptr () -> Maybe c -> m ()
- genClosure_TaskThreadFunc :: TaskThreadFunc -> IO Closure
- mk_TaskThreadFunc :: C_TaskThreadFunc -> IO (FunPtr C_TaskThreadFunc)
- noTaskThreadFunc :: Maybe TaskThreadFunc
- wrap_TaskThreadFunc :: Maybe (Ptr (FunPtr C_TaskThreadFunc)) -> TaskThreadFunc -> C_TaskThreadFunc
- type C_VfsFileLookupFunc = Ptr Vfs -> CString -> Ptr () -> IO (Ptr File)
- type VfsFileLookupFunc = Vfs -> Text -> IO File
- type VfsFileLookupFunc_WithClosures = Vfs -> Text -> Ptr () -> IO File
- drop_closures_VfsFileLookupFunc :: VfsFileLookupFunc -> VfsFileLookupFunc_WithClosures
- dynamic_VfsFileLookupFunc :: (HasCallStack, MonadIO m, IsVfs a) => FunPtr C_VfsFileLookupFunc -> a -> Text -> Ptr () -> m File
- genClosure_VfsFileLookupFunc :: VfsFileLookupFunc -> IO Closure
- mk_VfsFileLookupFunc :: C_VfsFileLookupFunc -> IO (FunPtr C_VfsFileLookupFunc)
- noVfsFileLookupFunc :: Maybe VfsFileLookupFunc
- noVfsFileLookupFunc_WithClosures :: Maybe VfsFileLookupFunc_WithClosures
- wrap_VfsFileLookupFunc :: Maybe (Ptr (FunPtr C_VfsFileLookupFunc)) -> VfsFileLookupFunc_WithClosures -> C_VfsFileLookupFunc
Signals
ActionEntryActivateFieldCallback
type ActionEntryActivateFieldCallback = SimpleAction -> Maybe GVariant -> IO () Source #
No description available in the introspection data.
type ActionEntryActivateFieldCallback_WithClosures = SimpleAction -> Maybe GVariant -> Ptr () -> IO () Source #
No description available in the introspection data.
type C_ActionEntryActivateFieldCallback = Ptr SimpleAction -> Ptr GVariant -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_ActionEntryActivateFieldCallback :: ActionEntryActivateFieldCallback -> ActionEntryActivateFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ActionEntryActivateFieldCallback :: (HasCallStack, MonadIO m, IsSimpleAction a) => FunPtr C_ActionEntryActivateFieldCallback -> a -> Maybe GVariant -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ActionEntryActivateFieldCallback :: ActionEntryActivateFieldCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_ActionEntryActivateFieldCallback :: C_ActionEntryActivateFieldCallback -> IO (FunPtr C_ActionEntryActivateFieldCallback) Source #
Generate a function pointer callable from C code, from a C_ActionEntryActivateFieldCallback
.
noActionEntryActivateFieldCallback :: Maybe ActionEntryActivateFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
ActionEntryActivateFieldCallback
noActionEntryActivateFieldCallback_WithClosures :: Maybe ActionEntryActivateFieldCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ActionEntryActivateFieldCallback_WithClosures
wrap_ActionEntryActivateFieldCallback :: Maybe (Ptr (FunPtr C_ActionEntryActivateFieldCallback)) -> ActionEntryActivateFieldCallback_WithClosures -> C_ActionEntryActivateFieldCallback Source #
ActionEntryChangeStateFieldCallback
type ActionEntryChangeStateFieldCallback = SimpleAction -> GVariant -> IO () Source #
No description available in the introspection data.
type ActionEntryChangeStateFieldCallback_WithClosures = SimpleAction -> GVariant -> Ptr () -> IO () Source #
No description available in the introspection data.
type C_ActionEntryChangeStateFieldCallback = Ptr SimpleAction -> Ptr GVariant -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_ActionEntryChangeStateFieldCallback :: ActionEntryChangeStateFieldCallback -> ActionEntryChangeStateFieldCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_ActionEntryChangeStateFieldCallback :: (HasCallStack, MonadIO m, IsSimpleAction a) => FunPtr C_ActionEntryChangeStateFieldCallback -> a -> GVariant -> Ptr () -> m () Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ActionEntryChangeStateFieldCallback :: ActionEntryChangeStateFieldCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_ActionEntryChangeStateFieldCallback :: C_ActionEntryChangeStateFieldCallback -> IO (FunPtr C_ActionEntryChangeStateFieldCallback) Source #
Generate a function pointer callable from C code, from a C_ActionEntryChangeStateFieldCallback
.
noActionEntryChangeStateFieldCallback :: Maybe ActionEntryChangeStateFieldCallback Source #
A convenience synonym for
.Nothing
:: Maybe
ActionEntryChangeStateFieldCallback
noActionEntryChangeStateFieldCallback_WithClosures :: Maybe ActionEntryChangeStateFieldCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
ActionEntryChangeStateFieldCallback_WithClosures
wrap_ActionEntryChangeStateFieldCallback :: Maybe (Ptr (FunPtr C_ActionEntryChangeStateFieldCallback)) -> ActionEntryChangeStateFieldCallback_WithClosures -> C_ActionEntryChangeStateFieldCallback Source #
AsyncReadyCallback
type AsyncReadyCallback Source #
= Maybe Object |
|
-> AsyncResult |
|
-> IO () |
Type definition for a function that will be called back when an asynchronous
operation within GIO has been completed. AsyncReadyCallback
callbacks from Task
are guaranteed to be invoked in a later
iteration of the
[thread-default main context][g-main-context-push-thread-default]
where the Task
was created. All other users of
AsyncReadyCallback
must likewise call it asynchronously in a
later iteration of the main context.
type AsyncReadyCallback_WithClosures Source #
= Maybe Object |
|
-> AsyncResult |
|
-> Ptr () |
|
-> IO () |
Type definition for a function that will be called back when an asynchronous
operation within GIO has been completed. AsyncReadyCallback
callbacks from Task
are guaranteed to be invoked in a later
iteration of the
[thread-default main context][g-main-context-push-thread-default]
where the Task
was created. All other users of
AsyncReadyCallback
must likewise call it asynchronously in a
later iteration of the main context.
type C_AsyncReadyCallback = Ptr Object -> Ptr AsyncResult -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_AsyncReadyCallback :: AsyncReadyCallback -> AsyncReadyCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_AsyncReadyCallback Source #
:: (HasCallStack, MonadIO m, IsObject a, IsAsyncResult b) | |
=> FunPtr C_AsyncReadyCallback | |
-> Maybe a |
|
-> b |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_AsyncReadyCallback :: AsyncReadyCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_AsyncReadyCallback :: C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback) Source #
Generate a function pointer callable from C code, from a C_AsyncReadyCallback
.
noAsyncReadyCallback :: Maybe AsyncReadyCallback Source #
A convenience synonym for
.Nothing
:: Maybe
AsyncReadyCallback
noAsyncReadyCallback_WithClosures :: Maybe AsyncReadyCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
AsyncReadyCallback_WithClosures
wrap_AsyncReadyCallback :: Maybe (Ptr (FunPtr C_AsyncReadyCallback)) -> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback Source #
Wrap a AsyncReadyCallback
into a C_AsyncReadyCallback
.
BusAcquiredCallback
type BusAcquiredCallback Source #
= DBusConnection |
|
-> Text |
|
-> IO () |
Invoked when a connection to a message bus has been obtained.
Since: 2.26
type BusAcquiredCallback_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Ptr () |
|
-> IO () |
Invoked when a connection to a message bus has been obtained.
Since: 2.26
type C_BusAcquiredCallback = Ptr DBusConnection -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BusAcquiredCallback :: BusAcquiredCallback -> BusAcquiredCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BusAcquiredCallback Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_BusAcquiredCallback | |
-> a |
|
-> Text |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BusAcquiredCallback :: BusAcquiredCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_BusAcquiredCallback :: C_BusAcquiredCallback -> IO (FunPtr C_BusAcquiredCallback) Source #
Generate a function pointer callable from C code, from a C_BusAcquiredCallback
.
noBusAcquiredCallback :: Maybe BusAcquiredCallback Source #
A convenience synonym for
.Nothing
:: Maybe
BusAcquiredCallback
noBusAcquiredCallback_WithClosures :: Maybe BusAcquiredCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BusAcquiredCallback_WithClosures
wrap_BusAcquiredCallback :: Maybe (Ptr (FunPtr C_BusAcquiredCallback)) -> BusAcquiredCallback_WithClosures -> C_BusAcquiredCallback Source #
Wrap a BusAcquiredCallback
into a C_BusAcquiredCallback
.
BusNameAcquiredCallback
type BusNameAcquiredCallback Source #
= DBusConnection |
|
-> Text |
|
-> IO () |
Invoked when the name is acquired.
Since: 2.26
type BusNameAcquiredCallback_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Ptr () |
|
-> IO () |
Invoked when the name is acquired.
Since: 2.26
type C_BusNameAcquiredCallback = Ptr DBusConnection -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BusNameAcquiredCallback :: BusNameAcquiredCallback -> BusNameAcquiredCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BusNameAcquiredCallback Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_BusNameAcquiredCallback | |
-> a |
|
-> Text |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BusNameAcquiredCallback :: BusNameAcquiredCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_BusNameAcquiredCallback :: C_BusNameAcquiredCallback -> IO (FunPtr C_BusNameAcquiredCallback) Source #
Generate a function pointer callable from C code, from a C_BusNameAcquiredCallback
.
noBusNameAcquiredCallback :: Maybe BusNameAcquiredCallback Source #
A convenience synonym for
.Nothing
:: Maybe
BusNameAcquiredCallback
noBusNameAcquiredCallback_WithClosures :: Maybe BusNameAcquiredCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BusNameAcquiredCallback_WithClosures
wrap_BusNameAcquiredCallback :: Maybe (Ptr (FunPtr C_BusNameAcquiredCallback)) -> BusNameAcquiredCallback_WithClosures -> C_BusNameAcquiredCallback Source #
Wrap a BusNameAcquiredCallback
into a C_BusNameAcquiredCallback
.
BusNameAppearedCallback
type BusNameAppearedCallback Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> IO () |
Invoked when the name being watched is known to have to have a owner.
Since: 2.26
type BusNameAppearedCallback_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Ptr () |
|
-> IO () |
Invoked when the name being watched is known to have to have a owner.
Since: 2.26
type C_BusNameAppearedCallback = Ptr DBusConnection -> CString -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BusNameAppearedCallback :: BusNameAppearedCallback -> BusNameAppearedCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BusNameAppearedCallback Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_BusNameAppearedCallback | |
-> a |
|
-> Text |
|
-> Text |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BusNameAppearedCallback :: BusNameAppearedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_BusNameAppearedCallback :: C_BusNameAppearedCallback -> IO (FunPtr C_BusNameAppearedCallback) Source #
Generate a function pointer callable from C code, from a C_BusNameAppearedCallback
.
noBusNameAppearedCallback :: Maybe BusNameAppearedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
BusNameAppearedCallback
noBusNameAppearedCallback_WithClosures :: Maybe BusNameAppearedCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BusNameAppearedCallback_WithClosures
wrap_BusNameAppearedCallback :: Maybe (Ptr (FunPtr C_BusNameAppearedCallback)) -> BusNameAppearedCallback_WithClosures -> C_BusNameAppearedCallback Source #
Wrap a BusNameAppearedCallback
into a C_BusNameAppearedCallback
.
BusNameLostCallback
type BusNameLostCallback Source #
= DBusConnection |
|
-> Text |
|
-> IO () |
Invoked when the name is lost or connection
has been closed.
Since: 2.26
type BusNameLostCallback_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Ptr () |
|
-> IO () |
Invoked when the name is lost or connection
has been closed.
Since: 2.26
type C_BusNameLostCallback = Ptr DBusConnection -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BusNameLostCallback :: BusNameLostCallback -> BusNameLostCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BusNameLostCallback Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_BusNameLostCallback | |
-> a |
|
-> Text |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BusNameLostCallback :: BusNameLostCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_BusNameLostCallback :: C_BusNameLostCallback -> IO (FunPtr C_BusNameLostCallback) Source #
Generate a function pointer callable from C code, from a C_BusNameLostCallback
.
noBusNameLostCallback :: Maybe BusNameLostCallback Source #
A convenience synonym for
.Nothing
:: Maybe
BusNameLostCallback
noBusNameLostCallback_WithClosures :: Maybe BusNameLostCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BusNameLostCallback_WithClosures
wrap_BusNameLostCallback :: Maybe (Ptr (FunPtr C_BusNameLostCallback)) -> BusNameLostCallback_WithClosures -> C_BusNameLostCallback Source #
Wrap a BusNameLostCallback
into a C_BusNameLostCallback
.
BusNameVanishedCallback
type BusNameVanishedCallback Source #
= DBusConnection |
|
-> Text |
|
-> IO () |
Invoked when the name being watched is known not to have to have a owner.
This is also invoked when the DBusConnection
on which the watch was
established has been closed. In that case, connection
will be
Nothing
.
Since: 2.26
type BusNameVanishedCallback_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Ptr () |
|
-> IO () |
Invoked when the name being watched is known not to have to have a owner.
This is also invoked when the DBusConnection
on which the watch was
established has been closed. In that case, connection
will be
Nothing
.
Since: 2.26
type C_BusNameVanishedCallback = Ptr DBusConnection -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
drop_closures_BusNameVanishedCallback :: BusNameVanishedCallback -> BusNameVanishedCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_BusNameVanishedCallback Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_BusNameVanishedCallback | |
-> a |
|
-> Text |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_BusNameVanishedCallback :: BusNameVanishedCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_BusNameVanishedCallback :: C_BusNameVanishedCallback -> IO (FunPtr C_BusNameVanishedCallback) Source #
Generate a function pointer callable from C code, from a C_BusNameVanishedCallback
.
noBusNameVanishedCallback :: Maybe BusNameVanishedCallback Source #
A convenience synonym for
.Nothing
:: Maybe
BusNameVanishedCallback
noBusNameVanishedCallback_WithClosures :: Maybe BusNameVanishedCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
BusNameVanishedCallback_WithClosures
wrap_BusNameVanishedCallback :: Maybe (Ptr (FunPtr C_BusNameVanishedCallback)) -> BusNameVanishedCallback_WithClosures -> C_BusNameVanishedCallback Source #
Wrap a BusNameVanishedCallback
into a C_BusNameVanishedCallback
.
CancellableSourceFunc
type C_CancellableSourceFunc = Ptr Cancellable -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type CancellableSourceFunc Source #
= Maybe Cancellable |
|
-> IO Bool | Returns: it should return |
This is the function type of the callback used for the Source
returned by g_cancellable_source_new()
.
Since: 2.28
type CancellableSourceFunc_WithClosures Source #
= Maybe Cancellable |
|
-> Ptr () |
|
-> IO Bool | Returns: it should return |
This is the function type of the callback used for the Source
returned by g_cancellable_source_new()
.
Since: 2.28
drop_closures_CancellableSourceFunc :: CancellableSourceFunc -> CancellableSourceFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_CancellableSourceFunc Source #
:: (HasCallStack, MonadIO m, IsCancellable a) | |
=> FunPtr C_CancellableSourceFunc | |
-> Maybe a |
|
-> Ptr () |
|
-> m Bool | Returns: it should return |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_CancellableSourceFunc :: CancellableSourceFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_CancellableSourceFunc :: C_CancellableSourceFunc -> IO (FunPtr C_CancellableSourceFunc) Source #
Generate a function pointer callable from C code, from a C_CancellableSourceFunc
.
noCancellableSourceFunc :: Maybe CancellableSourceFunc Source #
A convenience synonym for
.Nothing
:: Maybe
CancellableSourceFunc
noCancellableSourceFunc_WithClosures :: Maybe CancellableSourceFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
CancellableSourceFunc_WithClosures
wrap_CancellableSourceFunc :: Maybe (Ptr (FunPtr C_CancellableSourceFunc)) -> CancellableSourceFunc_WithClosures -> C_CancellableSourceFunc Source #
Wrap a CancellableSourceFunc
into a C_CancellableSourceFunc
.
DBusInterfaceGetPropertyFunc
type C_DBusInterfaceGetPropertyFunc = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr GError -> Ptr () -> IO (Ptr GVariant) Source #
Type for the callback on the (unwrapped) C side.
type DBusInterfaceGetPropertyFunc Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GError |
|
-> IO GVariant | Returns: A |
The type of the getProperty
function in DBusInterfaceVTable
.
Since: 2.26
type DBusInterfaceGetPropertyFunc_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GError |
|
-> Ptr () |
|
-> IO GVariant | Returns: A |
The type of the getProperty
function in DBusInterfaceVTable
.
Since: 2.26
drop_closures_DBusInterfaceGetPropertyFunc :: DBusInterfaceGetPropertyFunc -> DBusInterfaceGetPropertyFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DBusInterfaceGetPropertyFunc Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_DBusInterfaceGetPropertyFunc | |
-> a |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GError |
|
-> Ptr () |
|
-> m GVariant | Returns: A |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DBusInterfaceGetPropertyFunc :: DBusInterfaceGetPropertyFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DBusInterfaceGetPropertyFunc :: C_DBusInterfaceGetPropertyFunc -> IO (FunPtr C_DBusInterfaceGetPropertyFunc) Source #
Generate a function pointer callable from C code, from a C_DBusInterfaceGetPropertyFunc
.
noDBusInterfaceGetPropertyFunc :: Maybe DBusInterfaceGetPropertyFunc Source #
A convenience synonym for
.Nothing
:: Maybe
DBusInterfaceGetPropertyFunc
noDBusInterfaceGetPropertyFunc_WithClosures :: Maybe DBusInterfaceGetPropertyFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DBusInterfaceGetPropertyFunc_WithClosures
wrap_DBusInterfaceGetPropertyFunc :: Maybe (Ptr (FunPtr C_DBusInterfaceGetPropertyFunc)) -> DBusInterfaceGetPropertyFunc_WithClosures -> C_DBusInterfaceGetPropertyFunc Source #
Wrap a DBusInterfaceGetPropertyFunc
into a C_DBusInterfaceGetPropertyFunc
.
DBusInterfaceMethodCallFunc
type C_DBusInterfaceMethodCallFunc = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr GVariant -> Ptr DBusMethodInvocation -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type DBusInterfaceMethodCallFunc Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GVariant |
|
-> DBusMethodInvocation |
|
-> IO () |
The type of the methodCall
function in DBusInterfaceVTable
.
Since: 2.26
type DBusInterfaceMethodCallFunc_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GVariant |
|
-> DBusMethodInvocation |
|
-> Ptr () |
|
-> IO () |
The type of the methodCall
function in DBusInterfaceVTable
.
Since: 2.26
drop_closures_DBusInterfaceMethodCallFunc :: DBusInterfaceMethodCallFunc -> DBusInterfaceMethodCallFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DBusInterfaceMethodCallFunc Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a, IsDBusMethodInvocation b) | |
=> FunPtr C_DBusInterfaceMethodCallFunc | |
-> a |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GVariant |
|
-> b |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DBusInterfaceMethodCallFunc :: DBusInterfaceMethodCallFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DBusInterfaceMethodCallFunc :: C_DBusInterfaceMethodCallFunc -> IO (FunPtr C_DBusInterfaceMethodCallFunc) Source #
Generate a function pointer callable from C code, from a C_DBusInterfaceMethodCallFunc
.
noDBusInterfaceMethodCallFunc :: Maybe DBusInterfaceMethodCallFunc Source #
A convenience synonym for
.Nothing
:: Maybe
DBusInterfaceMethodCallFunc
noDBusInterfaceMethodCallFunc_WithClosures :: Maybe DBusInterfaceMethodCallFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DBusInterfaceMethodCallFunc_WithClosures
wrap_DBusInterfaceMethodCallFunc :: Maybe (Ptr (FunPtr C_DBusInterfaceMethodCallFunc)) -> DBusInterfaceMethodCallFunc_WithClosures -> C_DBusInterfaceMethodCallFunc Source #
Wrap a DBusInterfaceMethodCallFunc
into a C_DBusInterfaceMethodCallFunc
.
DBusInterfaceSetPropertyFunc
type C_DBusInterfaceSetPropertyFunc = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr GVariant -> Ptr GError -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type DBusInterfaceSetPropertyFunc Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GVariant |
|
-> GError |
|
-> IO Bool | Returns: |
The type of the setProperty
function in DBusInterfaceVTable
.
Since: 2.26
type DBusInterfaceSetPropertyFunc_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GVariant |
|
-> GError |
|
-> Ptr () |
|
-> IO Bool | Returns: |
The type of the setProperty
function in DBusInterfaceVTable
.
Since: 2.26
drop_closures_DBusInterfaceSetPropertyFunc :: DBusInterfaceSetPropertyFunc -> DBusInterfaceSetPropertyFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DBusInterfaceSetPropertyFunc Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_DBusInterfaceSetPropertyFunc | |
-> a |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GVariant |
|
-> GError |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DBusInterfaceSetPropertyFunc :: DBusInterfaceSetPropertyFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DBusInterfaceSetPropertyFunc :: C_DBusInterfaceSetPropertyFunc -> IO (FunPtr C_DBusInterfaceSetPropertyFunc) Source #
Generate a function pointer callable from C code, from a C_DBusInterfaceSetPropertyFunc
.
noDBusInterfaceSetPropertyFunc :: Maybe DBusInterfaceSetPropertyFunc Source #
A convenience synonym for
.Nothing
:: Maybe
DBusInterfaceSetPropertyFunc
noDBusInterfaceSetPropertyFunc_WithClosures :: Maybe DBusInterfaceSetPropertyFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DBusInterfaceSetPropertyFunc_WithClosures
wrap_DBusInterfaceSetPropertyFunc :: Maybe (Ptr (FunPtr C_DBusInterfaceSetPropertyFunc)) -> DBusInterfaceSetPropertyFunc_WithClosures -> C_DBusInterfaceSetPropertyFunc Source #
Wrap a DBusInterfaceSetPropertyFunc
into a C_DBusInterfaceSetPropertyFunc
.
DBusMessageFilterFunction
type C_DBusMessageFilterFunction = Ptr DBusConnection -> Ptr DBusMessage -> CInt -> Ptr () -> IO (Ptr DBusMessage) Source #
Type for the callback on the (unwrapped) C side.
type DBusMessageFilterFunction Source #
= DBusConnection |
|
-> DBusMessage |
|
-> Bool |
|
-> IO (Maybe DBusMessage) | Returns: A |
Signature for function used in dBusConnectionAddFilter
.
A filter function is passed a DBusMessage
and expected to return
a DBusMessage
too. Passive filter functions that don't modify the
message can simply return the message
object:
>
>static GDBusMessage *
>passive_filter (GDBusConnection *connection
> GDBusMessage *message,
> gboolean incoming,
> gpointer user_data)
>{
> // inspect @message
> return message;
>}
Filter functions that wants to drop a message can simply return Nothing
:
>
>static GDBusMessage *
>drop_filter (GDBusConnection *connection
> GDBusMessage *message,
> gboolean incoming,
> gpointer user_data)
>{
> if (should_drop_message)
> {
> g_object_unref (message);
> message = NULL;
> }
> return message;
>}
Finally, a filter function may modify a message by copying it:
>
>static GDBusMessage *
>modifying_filter (GDBusConnection *connection
> GDBusMessage *message,
> gboolean incoming,
> gpointer user_data)
>{
> GDBusMessage *copy;
> GError *error;
>
> error = NULL;
> copy = g_dbus_message_copy (message, &error);
> // handle error being set
> g_object_unref (message);
>
> // modify
copy
>
> return copy;
>}
If the returned DBusMessage
is different from message
and cannot
be sent on connection
(it could use features, such as file
descriptors, not compatible with connection
), then a warning is
logged to standard error. Applications can
check this ahead of time using dBusMessageToBlob
passing a
DBusCapabilityFlags
value obtained from connection
.
Since: 2.26
type DBusMessageFilterFunction_WithClosures Source #
= DBusConnection |
|
-> DBusMessage |
|
-> Bool |
|
-> Ptr () |
|
-> IO (Maybe DBusMessage) | Returns: A |
Signature for function used in dBusConnectionAddFilter
.
A filter function is passed a DBusMessage
and expected to return
a DBusMessage
too. Passive filter functions that don't modify the
message can simply return the message
object:
>
>static GDBusMessage *
>passive_filter (GDBusConnection *connection
> GDBusMessage *message,
> gboolean incoming,
> gpointer user_data)
>{
> // inspect @message
> return message;
>}
Filter functions that wants to drop a message can simply return Nothing
:
>
>static GDBusMessage *
>drop_filter (GDBusConnection *connection
> GDBusMessage *message,
> gboolean incoming,
> gpointer user_data)
>{
> if (should_drop_message)
> {
> g_object_unref (message);
> message = NULL;
> }
> return message;
>}
Finally, a filter function may modify a message by copying it:
>
>static GDBusMessage *
>modifying_filter (GDBusConnection *connection
> GDBusMessage *message,
> gboolean incoming,
> gpointer user_data)
>{
> GDBusMessage *copy;
> GError *error;
>
> error = NULL;
> copy = g_dbus_message_copy (message, &error);
> // handle error being set
> g_object_unref (message);
>
> // modify
copy
>
> return copy;
>}
If the returned DBusMessage
is different from message
and cannot
be sent on connection
(it could use features, such as file
descriptors, not compatible with connection
), then a warning is
logged to standard error. Applications can
check this ahead of time using dBusMessageToBlob
passing a
DBusCapabilityFlags
value obtained from connection
.
Since: 2.26
drop_closures_DBusMessageFilterFunction :: DBusMessageFilterFunction -> DBusMessageFilterFunction_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DBusMessageFilterFunction Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a, IsDBusMessage b) | |
=> FunPtr C_DBusMessageFilterFunction | |
-> a |
|
-> b |
|
-> Bool |
|
-> Ptr () |
|
-> m (Maybe DBusMessage) | Returns: A |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DBusMessageFilterFunction :: DBusMessageFilterFunction -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DBusMessageFilterFunction :: C_DBusMessageFilterFunction -> IO (FunPtr C_DBusMessageFilterFunction) Source #
Generate a function pointer callable from C code, from a C_DBusMessageFilterFunction
.
noDBusMessageFilterFunction :: Maybe DBusMessageFilterFunction Source #
A convenience synonym for
.Nothing
:: Maybe
DBusMessageFilterFunction
noDBusMessageFilterFunction_WithClosures :: Maybe DBusMessageFilterFunction_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DBusMessageFilterFunction_WithClosures
wrap_DBusMessageFilterFunction :: Maybe (Ptr (FunPtr C_DBusMessageFilterFunction)) -> DBusMessageFilterFunction_WithClosures -> C_DBusMessageFilterFunction Source #
Wrap a DBusMessageFilterFunction
into a C_DBusMessageFilterFunction
.
DBusProxyTypeFunc
type C_DBusProxyTypeFunc = Ptr DBusObjectManagerClient -> CString -> CString -> Ptr () -> IO CGType Source #
Type for the callback on the (unwrapped) C side.
type DBusProxyTypeFunc Source #
= DBusObjectManagerClient |
|
-> Text |
|
-> Maybe Text |
|
-> IO GType | Returns: A |
Function signature for a function used to determine the GType
to
use for an interface proxy (if interfaceName
is not Nothing
) or
object proxy (if interfaceName
is Nothing
).
This function is called in the
[thread-default main loop][g-main-context-push-thread-default]
that manager
was constructed in.
Since: 2.30
type DBusProxyTypeFunc_WithClosures Source #
= DBusObjectManagerClient |
|
-> Text |
|
-> Maybe Text |
|
-> Ptr () |
|
-> IO GType | Returns: A |
Function signature for a function used to determine the GType
to
use for an interface proxy (if interfaceName
is not Nothing
) or
object proxy (if interfaceName
is Nothing
).
This function is called in the
[thread-default main loop][g-main-context-push-thread-default]
that manager
was constructed in.
Since: 2.30
drop_closures_DBusProxyTypeFunc :: DBusProxyTypeFunc -> DBusProxyTypeFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DBusProxyTypeFunc Source #
:: (HasCallStack, MonadIO m, IsDBusObjectManagerClient a) | |
=> FunPtr C_DBusProxyTypeFunc | |
-> a |
|
-> Text |
|
-> Maybe Text |
|
-> Ptr () |
|
-> m GType | Returns: A |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DBusProxyTypeFunc :: DBusProxyTypeFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DBusProxyTypeFunc :: C_DBusProxyTypeFunc -> IO (FunPtr C_DBusProxyTypeFunc) Source #
Generate a function pointer callable from C code, from a C_DBusProxyTypeFunc
.
noDBusProxyTypeFunc :: Maybe DBusProxyTypeFunc Source #
A convenience synonym for
.Nothing
:: Maybe
DBusProxyTypeFunc
noDBusProxyTypeFunc_WithClosures :: Maybe DBusProxyTypeFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DBusProxyTypeFunc_WithClosures
wrap_DBusProxyTypeFunc :: Maybe (Ptr (FunPtr C_DBusProxyTypeFunc)) -> DBusProxyTypeFunc_WithClosures -> C_DBusProxyTypeFunc Source #
Wrap a DBusProxyTypeFunc
into a C_DBusProxyTypeFunc
.
DBusSignalCallback
type C_DBusSignalCallback = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr GVariant -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type DBusSignalCallback Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GVariant |
|
-> IO () |
Signature for callback function used in dBusConnectionSignalSubscribe
.
Since: 2.26
type DBusSignalCallback_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GVariant |
|
-> Ptr () |
|
-> IO () |
Signature for callback function used in dBusConnectionSignalSubscribe
.
Since: 2.26
drop_closures_DBusSignalCallback :: DBusSignalCallback -> DBusSignalCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DBusSignalCallback Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_DBusSignalCallback | |
-> a |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> GVariant |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DBusSignalCallback :: DBusSignalCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DBusSignalCallback :: C_DBusSignalCallback -> IO (FunPtr C_DBusSignalCallback) Source #
Generate a function pointer callable from C code, from a C_DBusSignalCallback
.
noDBusSignalCallback :: Maybe DBusSignalCallback Source #
A convenience synonym for
.Nothing
:: Maybe
DBusSignalCallback
noDBusSignalCallback_WithClosures :: Maybe DBusSignalCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DBusSignalCallback_WithClosures
wrap_DBusSignalCallback :: Maybe (Ptr (FunPtr C_DBusSignalCallback)) -> DBusSignalCallback_WithClosures -> C_DBusSignalCallback Source #
Wrap a DBusSignalCallback
into a C_DBusSignalCallback
.
DBusSubtreeDispatchFunc
type C_DBusSubtreeDispatchFunc = Ptr DBusConnection -> CString -> CString -> CString -> CString -> Ptr () -> Ptr () -> IO (Ptr DBusInterfaceVTable) Source #
Type for the callback on the (unwrapped) C side.
type DBusSubtreeDispatchFunc Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Ptr () |
|
-> IO DBusInterfaceVTable | Returns: A |
The type of the dispatch
function in DBusSubtreeVTable
.
Subtrees are flat. node
, if non-Nothing
, is always exactly one
segment of the object path (ie: it never contains a slash).
Since: 2.26
type DBusSubtreeDispatchFunc_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Ptr () |
|
-> Ptr () |
|
-> IO DBusInterfaceVTable | Returns: A |
The type of the dispatch
function in DBusSubtreeVTable
.
Subtrees are flat. node
, if non-Nothing
, is always exactly one
segment of the object path (ie: it never contains a slash).
Since: 2.26
drop_closures_DBusSubtreeDispatchFunc :: DBusSubtreeDispatchFunc -> DBusSubtreeDispatchFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DBusSubtreeDispatchFunc Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_DBusSubtreeDispatchFunc | |
-> a |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Ptr () |
|
-> Ptr () |
|
-> m DBusInterfaceVTable | Returns: A |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DBusSubtreeDispatchFunc :: DBusSubtreeDispatchFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DBusSubtreeDispatchFunc :: C_DBusSubtreeDispatchFunc -> IO (FunPtr C_DBusSubtreeDispatchFunc) Source #
Generate a function pointer callable from C code, from a C_DBusSubtreeDispatchFunc
.
noDBusSubtreeDispatchFunc :: Maybe DBusSubtreeDispatchFunc Source #
A convenience synonym for
.Nothing
:: Maybe
DBusSubtreeDispatchFunc
noDBusSubtreeDispatchFunc_WithClosures :: Maybe DBusSubtreeDispatchFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DBusSubtreeDispatchFunc_WithClosures
wrap_DBusSubtreeDispatchFunc :: Maybe (Ptr (FunPtr C_DBusSubtreeDispatchFunc)) -> DBusSubtreeDispatchFunc_WithClosures -> C_DBusSubtreeDispatchFunc Source #
Wrap a DBusSubtreeDispatchFunc
into a C_DBusSubtreeDispatchFunc
.
DBusSubtreeIntrospectFunc
type C_DBusSubtreeIntrospectFunc = Ptr DBusConnection -> CString -> CString -> CString -> Ptr () -> IO (Ptr DBusInterfaceInfo) Source #
Type for the callback on the (unwrapped) C side.
type DBusSubtreeIntrospectFunc Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> IO DBusInterfaceInfo | Returns: A |
The type of the introspect
function in DBusSubtreeVTable
.
Subtrees are flat. node
, if non-Nothing
, is always exactly one
segment of the object path (ie: it never contains a slash).
This function should return Nothing
to indicate that there is no object
at this node.
If this function returns non-Nothing
, the return value is expected to
be a Nothing
-terminated array of pointers to DBusInterfaceInfo
structures describing the interfaces implemented by node
. This
array will have dBusInterfaceInfoUnref
called on each item
before being freed with free
.
The difference between returning Nothing
and an array containing zero
items is that the standard DBus interfaces will returned to the
remote introspector in the empty array case, but not in the Nothing
case.
Since: 2.26
type DBusSubtreeIntrospectFunc_WithClosures Source #
= DBusConnection |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Ptr () |
|
-> IO DBusInterfaceInfo | Returns: A |
The type of the introspect
function in DBusSubtreeVTable
.
Subtrees are flat. node
, if non-Nothing
, is always exactly one
segment of the object path (ie: it never contains a slash).
This function should return Nothing
to indicate that there is no object
at this node.
If this function returns non-Nothing
, the return value is expected to
be a Nothing
-terminated array of pointers to DBusInterfaceInfo
structures describing the interfaces implemented by node
. This
array will have dBusInterfaceInfoUnref
called on each item
before being freed with free
.
The difference between returning Nothing
and an array containing zero
items is that the standard DBus interfaces will returned to the
remote introspector in the empty array case, but not in the Nothing
case.
Since: 2.26
drop_closures_DBusSubtreeIntrospectFunc :: DBusSubtreeIntrospectFunc -> DBusSubtreeIntrospectFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DBusSubtreeIntrospectFunc Source #
:: (HasCallStack, MonadIO m, IsDBusConnection a) | |
=> FunPtr C_DBusSubtreeIntrospectFunc | |
-> a |
|
-> Text |
|
-> Text |
|
-> Text |
|
-> Ptr () |
|
-> m DBusInterfaceInfo | Returns: A |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DBusSubtreeIntrospectFunc :: DBusSubtreeIntrospectFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DBusSubtreeIntrospectFunc :: C_DBusSubtreeIntrospectFunc -> IO (FunPtr C_DBusSubtreeIntrospectFunc) Source #
Generate a function pointer callable from C code, from a C_DBusSubtreeIntrospectFunc
.
noDBusSubtreeIntrospectFunc :: Maybe DBusSubtreeIntrospectFunc Source #
A convenience synonym for
.Nothing
:: Maybe
DBusSubtreeIntrospectFunc
noDBusSubtreeIntrospectFunc_WithClosures :: Maybe DBusSubtreeIntrospectFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DBusSubtreeIntrospectFunc_WithClosures
wrap_DBusSubtreeIntrospectFunc :: Maybe (Ptr (FunPtr C_DBusSubtreeIntrospectFunc)) -> DBusSubtreeIntrospectFunc_WithClosures -> C_DBusSubtreeIntrospectFunc Source #
Wrap a DBusSubtreeIntrospectFunc
into a C_DBusSubtreeIntrospectFunc
.
DatagramBasedSourceFunc
type C_DatagramBasedSourceFunc = Ptr DatagramBased -> CUInt -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type DatagramBasedSourceFunc Source #
= DatagramBased |
|
-> [IOCondition] |
|
-> IO Bool | Returns: |
This is the function type of the callback used for the Source
returned by datagramBasedCreateSource
.
Since: 2.48
type DatagramBasedSourceFunc_WithClosures Source #
= DatagramBased |
|
-> [IOCondition] |
|
-> Ptr () |
|
-> IO Bool | Returns: |
This is the function type of the callback used for the Source
returned by datagramBasedCreateSource
.
Since: 2.48
drop_closures_DatagramBasedSourceFunc :: DatagramBasedSourceFunc -> DatagramBasedSourceFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DatagramBasedSourceFunc Source #
:: (HasCallStack, MonadIO m, IsDatagramBased a) | |
=> FunPtr C_DatagramBasedSourceFunc | |
-> a |
|
-> [IOCondition] |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DatagramBasedSourceFunc :: DatagramBasedSourceFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DatagramBasedSourceFunc :: C_DatagramBasedSourceFunc -> IO (FunPtr C_DatagramBasedSourceFunc) Source #
Generate a function pointer callable from C code, from a C_DatagramBasedSourceFunc
.
noDatagramBasedSourceFunc :: Maybe DatagramBasedSourceFunc Source #
A convenience synonym for
.Nothing
:: Maybe
DatagramBasedSourceFunc
noDatagramBasedSourceFunc_WithClosures :: Maybe DatagramBasedSourceFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DatagramBasedSourceFunc_WithClosures
wrap_DatagramBasedSourceFunc :: Maybe (Ptr (FunPtr C_DatagramBasedSourceFunc)) -> DatagramBasedSourceFunc_WithClosures -> C_DatagramBasedSourceFunc Source #
Wrap a DatagramBasedSourceFunc
into a C_DatagramBasedSourceFunc
.
DesktopAppLaunchCallback
type C_DesktopAppLaunchCallback = Ptr DesktopAppInfo -> Int32 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type DesktopAppLaunchCallback Source #
= DesktopAppInfo |
|
-> Int32 |
|
-> IO () |
During invocation, desktopAppInfoLaunchUrisAsManager
may
create one or more child processes. This callback is invoked once
for each, providing the process ID.
type DesktopAppLaunchCallback_WithClosures Source #
= DesktopAppInfo |
|
-> Int32 |
|
-> Ptr () |
|
-> IO () |
During invocation, desktopAppInfoLaunchUrisAsManager
may
create one or more child processes. This callback is invoked once
for each, providing the process ID.
drop_closures_DesktopAppLaunchCallback :: DesktopAppLaunchCallback -> DesktopAppLaunchCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_DesktopAppLaunchCallback Source #
:: (HasCallStack, MonadIO m, IsDesktopAppInfo a) | |
=> FunPtr C_DesktopAppLaunchCallback | |
-> a |
|
-> Int32 |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_DesktopAppLaunchCallback :: DesktopAppLaunchCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_DesktopAppLaunchCallback :: C_DesktopAppLaunchCallback -> IO (FunPtr C_DesktopAppLaunchCallback) Source #
Generate a function pointer callable from C code, from a C_DesktopAppLaunchCallback
.
noDesktopAppLaunchCallback :: Maybe DesktopAppLaunchCallback Source #
A convenience synonym for
.Nothing
:: Maybe
DesktopAppLaunchCallback
noDesktopAppLaunchCallback_WithClosures :: Maybe DesktopAppLaunchCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
DesktopAppLaunchCallback_WithClosures
wrap_DesktopAppLaunchCallback :: Maybe (Ptr (FunPtr C_DesktopAppLaunchCallback)) -> DesktopAppLaunchCallback_WithClosures -> C_DesktopAppLaunchCallback Source #
Wrap a DesktopAppLaunchCallback
into a C_DesktopAppLaunchCallback
.
FileMeasureProgressCallback
type C_FileMeasureProgressCallback = CInt -> Word64 -> Word64 -> Word64 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type FileMeasureProgressCallback Source #
= Bool |
|
-> Word64 |
|
-> Word64 |
|
-> Word64 |
|
-> IO () |
This callback type is used by g_file_measure_disk_usage()
to make
periodic progress reports when measuring the amount of disk spaced
used by a directory.
These calls are made on a best-effort basis and not all types of
File
will support them. At the minimum, however, one call will
always be made immediately.
In the case that there is no support, reporting
will be set to
False
(and the other values undefined) and no further calls will be
made. Otherwise, the reporting
will be True
and the other values
all-zeros during the first (immediate) call. In this way, you can
know which type of progress UI to show without a delay.
For g_file_measure_disk_usage()
the callback is made directly. For
g_file_measure_disk_usage_async()
the callback is made via the
default main context of the calling thread (ie: the same way that the
final async result would be reported).
currentSize
is in the same units as requested by the operation (see
G_FILE_DISK_USAGE_APPARENT_SIZE
).
The frequency of the updates is implementation defined, but is ideally about once every 200ms.
The last progress callback may or may not be equal to the final result. Always check the async result to get the final value.
Since: 2.38
type FileMeasureProgressCallback_WithClosures Source #
= Bool |
|
-> Word64 |
|
-> Word64 |
|
-> Word64 |
|
-> Ptr () |
|
-> IO () |
This callback type is used by g_file_measure_disk_usage()
to make
periodic progress reports when measuring the amount of disk spaced
used by a directory.
These calls are made on a best-effort basis and not all types of
File
will support them. At the minimum, however, one call will
always be made immediately.
In the case that there is no support, reporting
will be set to
False
(and the other values undefined) and no further calls will be
made. Otherwise, the reporting
will be True
and the other values
all-zeros during the first (immediate) call. In this way, you can
know which type of progress UI to show without a delay.
For g_file_measure_disk_usage()
the callback is made directly. For
g_file_measure_disk_usage_async()
the callback is made via the
default main context of the calling thread (ie: the same way that the
final async result would be reported).
currentSize
is in the same units as requested by the operation (see
G_FILE_DISK_USAGE_APPARENT_SIZE
).
The frequency of the updates is implementation defined, but is ideally about once every 200ms.
The last progress callback may or may not be equal to the final result. Always check the async result to get the final value.
Since: 2.38
drop_closures_FileMeasureProgressCallback :: FileMeasureProgressCallback -> FileMeasureProgressCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FileMeasureProgressCallback Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FileMeasureProgressCallback | |
-> Bool |
|
-> Word64 |
|
-> Word64 |
|
-> Word64 |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FileMeasureProgressCallback :: FileMeasureProgressCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_FileMeasureProgressCallback :: C_FileMeasureProgressCallback -> IO (FunPtr C_FileMeasureProgressCallback) Source #
Generate a function pointer callable from C code, from a C_FileMeasureProgressCallback
.
noFileMeasureProgressCallback :: Maybe FileMeasureProgressCallback Source #
A convenience synonym for
.Nothing
:: Maybe
FileMeasureProgressCallback
noFileMeasureProgressCallback_WithClosures :: Maybe FileMeasureProgressCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FileMeasureProgressCallback_WithClosures
wrap_FileMeasureProgressCallback :: Maybe (Ptr (FunPtr C_FileMeasureProgressCallback)) -> FileMeasureProgressCallback_WithClosures -> C_FileMeasureProgressCallback Source #
Wrap a FileMeasureProgressCallback
into a C_FileMeasureProgressCallback
.
FileProgressCallback
type C_FileProgressCallback = Int64 -> Int64 -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type FileProgressCallback Source #
= Int64 |
|
-> Int64 |
|
-> IO () |
When doing file operations that may take a while, such as moving a file or copying a file, a progress callback is used to pass how far along that operation is to the application.
type FileProgressCallback_WithClosures Source #
= Int64 |
|
-> Int64 |
|
-> Ptr () |
|
-> IO () |
When doing file operations that may take a while, such as moving a file or copying a file, a progress callback is used to pass how far along that operation is to the application.
drop_closures_FileProgressCallback :: FileProgressCallback -> FileProgressCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FileProgressCallback Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FileProgressCallback | |
-> Int64 |
|
-> Int64 |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FileProgressCallback :: FileProgressCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_FileProgressCallback :: C_FileProgressCallback -> IO (FunPtr C_FileProgressCallback) Source #
Generate a function pointer callable from C code, from a C_FileProgressCallback
.
noFileProgressCallback :: Maybe FileProgressCallback Source #
A convenience synonym for
.Nothing
:: Maybe
FileProgressCallback
noFileProgressCallback_WithClosures :: Maybe FileProgressCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FileProgressCallback_WithClosures
wrap_FileProgressCallback :: Maybe (Ptr (FunPtr C_FileProgressCallback)) -> FileProgressCallback_WithClosures -> C_FileProgressCallback Source #
Wrap a FileProgressCallback
into a C_FileProgressCallback
.
FileReadMoreCallback
type C_FileReadMoreCallback = CString -> Int64 -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type FileReadMoreCallback Source #
= Text |
|
-> Int64 |
|
-> IO Bool | Returns: |
When loading the partial contents of a file with g_file_load_partial_contents_async()
,
it may become necessary to determine if any more data from the file should be loaded.
A FileReadMoreCallback
function facilitates this by returning True
if more data
should be read, or False
otherwise.
type FileReadMoreCallback_WithClosures Source #
= Text |
|
-> Int64 |
|
-> Ptr () |
|
-> IO Bool | Returns: |
When loading the partial contents of a file with g_file_load_partial_contents_async()
,
it may become necessary to determine if any more data from the file should be loaded.
A FileReadMoreCallback
function facilitates this by returning True
if more data
should be read, or False
otherwise.
drop_closures_FileReadMoreCallback :: FileReadMoreCallback -> FileReadMoreCallback_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_FileReadMoreCallback Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_FileReadMoreCallback | |
-> Text |
|
-> Int64 |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_FileReadMoreCallback :: FileReadMoreCallback -> IO Closure Source #
Wrap the callback into a Closure
.
mk_FileReadMoreCallback :: C_FileReadMoreCallback -> IO (FunPtr C_FileReadMoreCallback) Source #
Generate a function pointer callable from C code, from a C_FileReadMoreCallback
.
noFileReadMoreCallback :: Maybe FileReadMoreCallback Source #
A convenience synonym for
.Nothing
:: Maybe
FileReadMoreCallback
noFileReadMoreCallback_WithClosures :: Maybe FileReadMoreCallback_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
FileReadMoreCallback_WithClosures
wrap_FileReadMoreCallback :: Maybe (Ptr (FunPtr C_FileReadMoreCallback)) -> FileReadMoreCallback_WithClosures -> C_FileReadMoreCallback Source #
Wrap a FileReadMoreCallback
into a C_FileReadMoreCallback
.
IOSchedulerJobFunc
type C_IOSchedulerJobFunc = Ptr IOSchedulerJob -> Ptr Cancellable -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type IOSchedulerJobFunc Source #
= IOSchedulerJob |
|
-> Maybe Cancellable |
|
-> IO Bool | Returns: |
I/O Job function.
Long-running jobs should periodically check the cancellable
to see if they have been cancelled.
type IOSchedulerJobFunc_WithClosures Source #
= IOSchedulerJob |
|
-> Maybe Cancellable |
|
-> Ptr () |
|
-> IO Bool | Returns: |
I/O Job function.
Long-running jobs should periodically check the cancellable
to see if they have been cancelled.
drop_closures_IOSchedulerJobFunc :: IOSchedulerJobFunc -> IOSchedulerJobFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_IOSchedulerJobFunc Source #
:: (HasCallStack, MonadIO m, IsCancellable a) | |
=> FunPtr C_IOSchedulerJobFunc | |
-> IOSchedulerJob |
|
-> Maybe a |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_IOSchedulerJobFunc :: IOSchedulerJobFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_IOSchedulerJobFunc :: C_IOSchedulerJobFunc -> IO (FunPtr C_IOSchedulerJobFunc) Source #
Generate a function pointer callable from C code, from a C_IOSchedulerJobFunc
.
noIOSchedulerJobFunc :: Maybe IOSchedulerJobFunc Source #
A convenience synonym for
.Nothing
:: Maybe
IOSchedulerJobFunc
noIOSchedulerJobFunc_WithClosures :: Maybe IOSchedulerJobFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
IOSchedulerJobFunc_WithClosures
wrap_IOSchedulerJobFunc :: Maybe (Ptr (FunPtr C_IOSchedulerJobFunc)) -> IOSchedulerJobFunc_WithClosures -> C_IOSchedulerJobFunc Source #
Wrap a IOSchedulerJobFunc
into a C_IOSchedulerJobFunc
.
PollableSourceFunc
type C_PollableSourceFunc = Ptr Object -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type PollableSourceFunc Source #
= Object |
|
-> IO Bool | Returns: it should return |
This is the function type of the callback used for the Source
returned by pollableInputStreamCreateSource
and
pollableOutputStreamCreateSource
.
Since: 2.28
type PollableSourceFunc_WithClosures Source #
= Object |
|
-> Ptr () |
|
-> IO Bool | Returns: it should return |
This is the function type of the callback used for the Source
returned by pollableInputStreamCreateSource
and
pollableOutputStreamCreateSource
.
Since: 2.28
drop_closures_PollableSourceFunc :: PollableSourceFunc -> PollableSourceFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_PollableSourceFunc Source #
:: (HasCallStack, MonadIO m, IsObject a) | |
=> FunPtr C_PollableSourceFunc | |
-> a |
|
-> Ptr () |
|
-> m Bool | Returns: it should return |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_PollableSourceFunc :: PollableSourceFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_PollableSourceFunc :: C_PollableSourceFunc -> IO (FunPtr C_PollableSourceFunc) Source #
Generate a function pointer callable from C code, from a C_PollableSourceFunc
.
noPollableSourceFunc :: Maybe PollableSourceFunc Source #
A convenience synonym for
.Nothing
:: Maybe
PollableSourceFunc
noPollableSourceFunc_WithClosures :: Maybe PollableSourceFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
PollableSourceFunc_WithClosures
wrap_PollableSourceFunc :: Maybe (Ptr (FunPtr C_PollableSourceFunc)) -> PollableSourceFunc_WithClosures -> C_PollableSourceFunc Source #
Wrap a PollableSourceFunc
into a C_PollableSourceFunc
.
ReallocFunc
type C_ReallocFunc = Ptr () -> Word64 -> IO (Ptr ()) Source #
Type for the callback on the (unwrapped) C side.
type ReallocFunc Source #
= Ptr () |
|
-> Word64 |
|
-> IO (Ptr ()) | Returns: a pointer to the reallocated memory |
Changes the size of the memory block pointed to by data
to
size
bytes.
The function should have the same semantics as realloc()
.
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_ReallocFunc | |
-> Ptr () |
|
-> Word64 |
|
-> m (Ptr ()) | Returns: a pointer to the reallocated memory |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_ReallocFunc :: ReallocFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_ReallocFunc :: C_ReallocFunc -> IO (FunPtr C_ReallocFunc) Source #
Generate a function pointer callable from C code, from a C_ReallocFunc
.
noReallocFunc :: Maybe ReallocFunc Source #
A convenience synonym for
.Nothing
:: Maybe
ReallocFunc
wrap_ReallocFunc :: Maybe (Ptr (FunPtr C_ReallocFunc)) -> ReallocFunc -> C_ReallocFunc Source #
Wrap a ReallocFunc
into a C_ReallocFunc
.
SettingsBindGetMapping
type C_SettingsBindGetMapping = Ptr GValue -> Ptr GVariant -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type SettingsBindGetMapping Source #
= GValue |
|
-> GVariant |
|
-> IO Bool | Returns: |
The type for the function that is used to convert from Settings
to
an object property. The value
is already initialized to hold values
of the appropriate type.
type SettingsBindGetMapping_WithClosures Source #
= GValue |
|
-> GVariant |
|
-> Ptr () |
|
-> IO Bool | Returns: |
The type for the function that is used to convert from Settings
to
an object property. The value
is already initialized to hold values
of the appropriate type.
drop_closures_SettingsBindGetMapping :: SettingsBindGetMapping -> SettingsBindGetMapping_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SettingsBindGetMapping Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_SettingsBindGetMapping | |
-> GValue |
|
-> GVariant |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SettingsBindGetMapping :: SettingsBindGetMapping -> IO Closure Source #
Wrap the callback into a Closure
.
mk_SettingsBindGetMapping :: C_SettingsBindGetMapping -> IO (FunPtr C_SettingsBindGetMapping) Source #
Generate a function pointer callable from C code, from a C_SettingsBindGetMapping
.
noSettingsBindGetMapping :: Maybe SettingsBindGetMapping Source #
A convenience synonym for
.Nothing
:: Maybe
SettingsBindGetMapping
noSettingsBindGetMapping_WithClosures :: Maybe SettingsBindGetMapping_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SettingsBindGetMapping_WithClosures
wrap_SettingsBindGetMapping :: Maybe (Ptr (FunPtr C_SettingsBindGetMapping)) -> SettingsBindGetMapping_WithClosures -> C_SettingsBindGetMapping Source #
Wrap a SettingsBindGetMapping
into a C_SettingsBindGetMapping
.
SettingsBindSetMapping
type C_SettingsBindSetMapping = Ptr GValue -> Ptr VariantType -> Ptr () -> IO (Ptr GVariant) Source #
Type for the callback on the (unwrapped) C side.
type SettingsBindSetMapping Source #
= GValue |
|
-> VariantType |
|
-> IO GVariant | Returns: a new |
type SettingsBindSetMapping_WithClosures Source #
= GValue |
|
-> VariantType |
|
-> Ptr () |
|
-> IO GVariant | Returns: a new |
drop_closures_SettingsBindSetMapping :: SettingsBindSetMapping -> SettingsBindSetMapping_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SettingsBindSetMapping Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_SettingsBindSetMapping | |
-> GValue |
|
-> VariantType |
|
-> Ptr () |
|
-> m GVariant | Returns: a new |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SettingsBindSetMapping :: SettingsBindSetMapping -> IO Closure Source #
Wrap the callback into a Closure
.
mk_SettingsBindSetMapping :: C_SettingsBindSetMapping -> IO (FunPtr C_SettingsBindSetMapping) Source #
Generate a function pointer callable from C code, from a C_SettingsBindSetMapping
.
noSettingsBindSetMapping :: Maybe SettingsBindSetMapping Source #
A convenience synonym for
.Nothing
:: Maybe
SettingsBindSetMapping
noSettingsBindSetMapping_WithClosures :: Maybe SettingsBindSetMapping_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SettingsBindSetMapping_WithClosures
wrap_SettingsBindSetMapping :: Maybe (Ptr (FunPtr C_SettingsBindSetMapping)) -> SettingsBindSetMapping_WithClosures -> C_SettingsBindSetMapping Source #
Wrap a SettingsBindSetMapping
into a C_SettingsBindSetMapping
.
SettingsGetMapping
type C_SettingsGetMapping = Ptr GVariant -> Ptr (Ptr ()) -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type SettingsGetMapping Source #
The type of the function that is used to convert from a value stored
in a Settings
to a value that is useful to the application.
If the value is successfully mapped, the result should be stored at
result
and True
returned. If mapping fails (for example, if value
is not in the right format) then False
should be returned.
If value
is Nothing
then it means that the mapping function is being
given a "last chance" to successfully return a valid value. True
must be returned in this case.
type SettingsGetMapping_WithClosures Source #
= GVariant | |
-> Ptr () |
|
-> IO (Bool, Ptr ()) | Returns: |
The type of the function that is used to convert from a value stored
in a Settings
to a value that is useful to the application.
If the value is successfully mapped, the result should be stored at
result
and True
returned. If mapping fails (for example, if value
is not in the right format) then False
should be returned.
If value
is Nothing
then it means that the mapping function is being
given a "last chance" to successfully return a valid value. True
must be returned in this case.
drop_closures_SettingsGetMapping :: SettingsGetMapping -> SettingsGetMapping_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SettingsGetMapping Source #
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_SettingsGetMapping | |
-> GVariant | |
-> Ptr () |
|
-> m (Bool, Ptr ()) | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SettingsGetMapping :: SettingsGetMapping -> IO Closure Source #
Wrap the callback into a Closure
.
mk_SettingsGetMapping :: C_SettingsGetMapping -> IO (FunPtr C_SettingsGetMapping) Source #
Generate a function pointer callable from C code, from a C_SettingsGetMapping
.
noSettingsGetMapping :: Maybe SettingsGetMapping Source #
A convenience synonym for
.Nothing
:: Maybe
SettingsGetMapping
noSettingsGetMapping_WithClosures :: Maybe SettingsGetMapping_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SettingsGetMapping_WithClosures
wrap_SettingsGetMapping :: Maybe (Ptr (FunPtr C_SettingsGetMapping)) -> SettingsGetMapping_WithClosures -> C_SettingsGetMapping Source #
Wrap a SettingsGetMapping
into a C_SettingsGetMapping
.
SimpleAsyncThreadFunc
type C_SimpleAsyncThreadFunc = Ptr SimpleAsyncResult -> Ptr Object -> Ptr Cancellable -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SimpleAsyncThreadFunc Source #
= SimpleAsyncResult |
|
-> Object |
|
-> Maybe Cancellable |
|
-> IO () |
Simple thread function that runs an asynchronous operation and checks for cancellation.
dynamic_SimpleAsyncThreadFunc Source #
:: (HasCallStack, MonadIO m, IsSimpleAsyncResult a, IsObject b, IsCancellable c) | |
=> FunPtr C_SimpleAsyncThreadFunc | |
-> a |
|
-> b |
|
-> Maybe c |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SimpleAsyncThreadFunc :: SimpleAsyncThreadFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_SimpleAsyncThreadFunc :: C_SimpleAsyncThreadFunc -> IO (FunPtr C_SimpleAsyncThreadFunc) Source #
Generate a function pointer callable from C code, from a C_SimpleAsyncThreadFunc
.
noSimpleAsyncThreadFunc :: Maybe SimpleAsyncThreadFunc Source #
A convenience synonym for
.Nothing
:: Maybe
SimpleAsyncThreadFunc
wrap_SimpleAsyncThreadFunc :: Maybe (Ptr (FunPtr C_SimpleAsyncThreadFunc)) -> SimpleAsyncThreadFunc -> C_SimpleAsyncThreadFunc Source #
Wrap a SimpleAsyncThreadFunc
into a C_SimpleAsyncThreadFunc
.
SocketSourceFunc
type C_SocketSourceFunc = Ptr Socket -> CUInt -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type SocketSourceFunc Source #
= Socket |
|
-> [IOCondition] |
|
-> IO Bool | Returns: it should return |
This is the function type of the callback used for the Source
returned by g_socket_create_source()
.
Since: 2.22
type SocketSourceFunc_WithClosures Source #
= Socket |
|
-> [IOCondition] |
|
-> Ptr () |
|
-> IO Bool | Returns: it should return |
This is the function type of the callback used for the Source
returned by g_socket_create_source()
.
Since: 2.22
drop_closures_SocketSourceFunc :: SocketSourceFunc -> SocketSourceFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SocketSourceFunc Source #
:: (HasCallStack, MonadIO m, IsSocket a) | |
=> FunPtr C_SocketSourceFunc | |
-> a |
|
-> [IOCondition] |
|
-> Ptr () |
|
-> m Bool | Returns: it should return |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SocketSourceFunc :: SocketSourceFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_SocketSourceFunc :: C_SocketSourceFunc -> IO (FunPtr C_SocketSourceFunc) Source #
Generate a function pointer callable from C code, from a C_SocketSourceFunc
.
noSocketSourceFunc :: Maybe SocketSourceFunc Source #
A convenience synonym for
.Nothing
:: Maybe
SocketSourceFunc
noSocketSourceFunc_WithClosures :: Maybe SocketSourceFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SocketSourceFunc_WithClosures
wrap_SocketSourceFunc :: Maybe (Ptr (FunPtr C_SocketSourceFunc)) -> SocketSourceFunc_WithClosures -> C_SocketSourceFunc Source #
Wrap a SocketSourceFunc
into a C_SocketSourceFunc
.
TaskThreadFunc
type C_TaskThreadFunc = Ptr Task -> Ptr Object -> Ptr () -> Ptr Cancellable -> IO () Source #
Type for the callback on the (unwrapped) C side.
type TaskThreadFunc Source #
= Task |
|
-> Object |
|
-> Ptr () |
|
-> Maybe Cancellable |
|
-> IO () |
The prototype for a task function to be run in a thread via
g_task_run_in_thread()
or g_task_run_in_thread_sync()
.
If the return-on-cancel flag is set on task
, and cancellable
gets
cancelled, then the Task
will be completed immediately (as though
taskReturnErrorIfCancelled
had been called), without
waiting for the task function to complete. However, the task
function will continue running in its thread in the background. The
function therefore needs to be careful about how it uses
externally-visible state in this case. See
taskSetReturnOnCancel
for more details.
Other than in that case, task
will be completed when the
TaskThreadFunc
returns, not when it calls a
g_task_return_
function.
Since: 2.36
dynamic_TaskThreadFunc Source #
:: (HasCallStack, MonadIO m, IsTask a, IsObject b, IsCancellable c) | |
=> FunPtr C_TaskThreadFunc | |
-> a |
|
-> b |
|
-> Ptr () |
|
-> Maybe c |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_TaskThreadFunc :: TaskThreadFunc -> IO Closure Source #
Wrap the callback into a Closure
.
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
wrap_TaskThreadFunc :: Maybe (Ptr (FunPtr C_TaskThreadFunc)) -> TaskThreadFunc -> C_TaskThreadFunc Source #
Wrap a TaskThreadFunc
into a C_TaskThreadFunc
.
VfsFileLookupFunc
type C_VfsFileLookupFunc = Ptr Vfs -> CString -> Ptr () -> IO (Ptr File) Source #
Type for the callback on the (unwrapped) C side.
type VfsFileLookupFunc Source #
= Vfs |
|
-> Text |
|
-> IO File | Returns: a |
This function type is used by vfsRegisterUriScheme
to make it
possible for a client to associate an URI scheme to a different File
implementation.
The client should return a reference to the new file that has been
created for uri
, or Nothing
to continue with the default implementation.
Since: 2.50
type VfsFileLookupFunc_WithClosures Source #
= Vfs |
|
-> Text |
|
-> Ptr () |
|
-> IO File | Returns: a |
This function type is used by vfsRegisterUriScheme
to make it
possible for a client to associate an URI scheme to a different File
implementation.
The client should return a reference to the new file that has been
created for uri
, or Nothing
to continue with the default implementation.
Since: 2.50
drop_closures_VfsFileLookupFunc :: VfsFileLookupFunc -> VfsFileLookupFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_VfsFileLookupFunc Source #
:: (HasCallStack, MonadIO m, IsVfs a) | |
=> FunPtr C_VfsFileLookupFunc | |
-> a |
|
-> Text |
|
-> Ptr () |
|
-> m File | Returns: a |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VfsFileLookupFunc :: VfsFileLookupFunc -> IO Closure Source #
Wrap the callback into a Closure
.
mk_VfsFileLookupFunc :: C_VfsFileLookupFunc -> IO (FunPtr C_VfsFileLookupFunc) Source #
Generate a function pointer callable from C code, from a C_VfsFileLookupFunc
.
noVfsFileLookupFunc :: Maybe VfsFileLookupFunc Source #
A convenience synonym for
.Nothing
:: Maybe
VfsFileLookupFunc
noVfsFileLookupFunc_WithClosures :: Maybe VfsFileLookupFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
VfsFileLookupFunc_WithClosures
wrap_VfsFileLookupFunc :: Maybe (Ptr (FunPtr C_VfsFileLookupFunc)) -> VfsFileLookupFunc_WithClosures -> C_VfsFileLookupFunc Source #
Wrap a VfsFileLookupFunc
into a C_VfsFileLookupFunc
.