Copyright | Will Thompson and Iñaki García Etxebarria |
---|---|
License | LGPL-2.1 |
Maintainer | Iñaki García Etxebarria |
Safe Haskell | None |
Language | Haskell2010 |
GI.NM.Callbacks
Description
Synopsis
- type C_KeyfileReadHandler = Ptr KeyFile -> Ptr Connection -> CUInt -> Ptr KeyfileHandlerData -> Ptr () -> IO CInt
- type KeyfileReadHandler = KeyFile -> Connection -> KeyfileHandlerType -> KeyfileHandlerData -> IO Bool
- type KeyfileReadHandler_WithClosures = KeyFile -> Connection -> KeyfileHandlerType -> KeyfileHandlerData -> Ptr () -> IO Bool
- drop_closures_KeyfileReadHandler :: KeyfileReadHandler -> KeyfileReadHandler_WithClosures
- dynamic_KeyfileReadHandler :: (HasCallStack, MonadIO m, IsConnection a) => FunPtr C_KeyfileReadHandler -> KeyFile -> a -> KeyfileHandlerType -> KeyfileHandlerData -> Ptr () -> m Bool
- genClosure_KeyfileReadHandler :: MonadIO m => KeyfileReadHandler -> m (GClosure C_KeyfileReadHandler)
- mk_KeyfileReadHandler :: C_KeyfileReadHandler -> IO (FunPtr C_KeyfileReadHandler)
- noKeyfileReadHandler :: Maybe KeyfileReadHandler
- noKeyfileReadHandler_WithClosures :: Maybe KeyfileReadHandler_WithClosures
- wrap_KeyfileReadHandler :: Maybe (Ptr (FunPtr C_KeyfileReadHandler)) -> KeyfileReadHandler_WithClosures -> C_KeyfileReadHandler
- type C_KeyfileWriteHandler = Ptr Connection -> Ptr KeyFile -> CUInt -> Ptr KeyfileHandlerData -> Ptr () -> IO CInt
- type KeyfileWriteHandler = Connection -> KeyFile -> KeyfileHandlerType -> KeyfileHandlerData -> IO Bool
- type KeyfileWriteHandler_WithClosures = Connection -> KeyFile -> KeyfileHandlerType -> KeyfileHandlerData -> Ptr () -> IO Bool
- drop_closures_KeyfileWriteHandler :: KeyfileWriteHandler -> KeyfileWriteHandler_WithClosures
- dynamic_KeyfileWriteHandler :: (HasCallStack, MonadIO m, IsConnection a) => FunPtr C_KeyfileWriteHandler -> a -> KeyFile -> KeyfileHandlerType -> KeyfileHandlerData -> Ptr () -> m Bool
- genClosure_KeyfileWriteHandler :: MonadIO m => KeyfileWriteHandler -> m (GClosure C_KeyfileWriteHandler)
- mk_KeyfileWriteHandler :: C_KeyfileWriteHandler -> IO (FunPtr C_KeyfileWriteHandler)
- noKeyfileWriteHandler :: Maybe KeyfileWriteHandler
- noKeyfileWriteHandler_WithClosures :: Maybe KeyfileWriteHandler_WithClosures
- wrap_KeyfileWriteHandler :: Maybe (Ptr (FunPtr C_KeyfileWriteHandler)) -> KeyfileWriteHandler_WithClosures -> C_KeyfileWriteHandler
- type C_SecretAgentOldDeleteSecretsFunc = Ptr SecretAgentOld -> Ptr Connection -> Ptr GError -> Ptr () -> IO ()
- type SecretAgentOldDeleteSecretsFunc = SecretAgentOld -> Connection -> GError -> IO ()
- type SecretAgentOldDeleteSecretsFunc_WithClosures = SecretAgentOld -> Connection -> GError -> Ptr () -> IO ()
- drop_closures_SecretAgentOldDeleteSecretsFunc :: SecretAgentOldDeleteSecretsFunc -> SecretAgentOldDeleteSecretsFunc_WithClosures
- dynamic_SecretAgentOldDeleteSecretsFunc :: (HasCallStack, MonadIO m, IsSecretAgentOld a, IsConnection b) => FunPtr C_SecretAgentOldDeleteSecretsFunc -> a -> b -> GError -> Ptr () -> m ()
- genClosure_SecretAgentOldDeleteSecretsFunc :: MonadIO m => SecretAgentOldDeleteSecretsFunc -> m (GClosure C_SecretAgentOldDeleteSecretsFunc)
- mk_SecretAgentOldDeleteSecretsFunc :: C_SecretAgentOldDeleteSecretsFunc -> IO (FunPtr C_SecretAgentOldDeleteSecretsFunc)
- noSecretAgentOldDeleteSecretsFunc :: Maybe SecretAgentOldDeleteSecretsFunc
- noSecretAgentOldDeleteSecretsFunc_WithClosures :: Maybe SecretAgentOldDeleteSecretsFunc_WithClosures
- wrap_SecretAgentOldDeleteSecretsFunc :: Maybe (Ptr (FunPtr C_SecretAgentOldDeleteSecretsFunc)) -> SecretAgentOldDeleteSecretsFunc_WithClosures -> C_SecretAgentOldDeleteSecretsFunc
- type C_SecretAgentOldGetSecretsFunc = Ptr SecretAgentOld -> Ptr Connection -> Ptr GVariant -> Ptr GError -> Ptr () -> IO ()
- type SecretAgentOldGetSecretsFunc = SecretAgentOld -> Connection -> GVariant -> GError -> IO ()
- type SecretAgentOldGetSecretsFunc_WithClosures = SecretAgentOld -> Connection -> GVariant -> GError -> Ptr () -> IO ()
- drop_closures_SecretAgentOldGetSecretsFunc :: SecretAgentOldGetSecretsFunc -> SecretAgentOldGetSecretsFunc_WithClosures
- dynamic_SecretAgentOldGetSecretsFunc :: (HasCallStack, MonadIO m, IsSecretAgentOld a, IsConnection b) => FunPtr C_SecretAgentOldGetSecretsFunc -> a -> b -> GVariant -> GError -> Ptr () -> m ()
- genClosure_SecretAgentOldGetSecretsFunc :: MonadIO m => SecretAgentOldGetSecretsFunc -> m (GClosure C_SecretAgentOldGetSecretsFunc)
- mk_SecretAgentOldGetSecretsFunc :: C_SecretAgentOldGetSecretsFunc -> IO (FunPtr C_SecretAgentOldGetSecretsFunc)
- noSecretAgentOldGetSecretsFunc :: Maybe SecretAgentOldGetSecretsFunc
- noSecretAgentOldGetSecretsFunc_WithClosures :: Maybe SecretAgentOldGetSecretsFunc_WithClosures
- wrap_SecretAgentOldGetSecretsFunc :: Maybe (Ptr (FunPtr C_SecretAgentOldGetSecretsFunc)) -> SecretAgentOldGetSecretsFunc_WithClosures -> C_SecretAgentOldGetSecretsFunc
- type C_SecretAgentOldSaveSecretsFunc = Ptr SecretAgentOld -> Ptr Connection -> Ptr GError -> Ptr () -> IO ()
- type SecretAgentOldSaveSecretsFunc = SecretAgentOld -> Connection -> GError -> IO ()
- type SecretAgentOldSaveSecretsFunc_WithClosures = SecretAgentOld -> Connection -> GError -> Ptr () -> IO ()
- drop_closures_SecretAgentOldSaveSecretsFunc :: SecretAgentOldSaveSecretsFunc -> SecretAgentOldSaveSecretsFunc_WithClosures
- dynamic_SecretAgentOldSaveSecretsFunc :: (HasCallStack, MonadIO m, IsSecretAgentOld a, IsConnection b) => FunPtr C_SecretAgentOldSaveSecretsFunc -> a -> b -> GError -> Ptr () -> m ()
- genClosure_SecretAgentOldSaveSecretsFunc :: MonadIO m => SecretAgentOldSaveSecretsFunc -> m (GClosure C_SecretAgentOldSaveSecretsFunc)
- mk_SecretAgentOldSaveSecretsFunc :: C_SecretAgentOldSaveSecretsFunc -> IO (FunPtr C_SecretAgentOldSaveSecretsFunc)
- noSecretAgentOldSaveSecretsFunc :: Maybe SecretAgentOldSaveSecretsFunc
- noSecretAgentOldSaveSecretsFunc_WithClosures :: Maybe SecretAgentOldSaveSecretsFunc_WithClosures
- wrap_SecretAgentOldSaveSecretsFunc :: Maybe (Ptr (FunPtr C_SecretAgentOldSaveSecretsFunc)) -> SecretAgentOldSaveSecretsFunc_WithClosures -> C_SecretAgentOldSaveSecretsFunc
- type C_SettingClearSecretsWithFlagsFn = Ptr Setting -> CString -> CUInt -> Ptr () -> IO CInt
- type SettingClearSecretsWithFlagsFn = Setting -> Text -> [SettingSecretFlags] -> IO Bool
- type SettingClearSecretsWithFlagsFn_WithClosures = Setting -> Text -> [SettingSecretFlags] -> Ptr () -> IO Bool
- drop_closures_SettingClearSecretsWithFlagsFn :: SettingClearSecretsWithFlagsFn -> SettingClearSecretsWithFlagsFn_WithClosures
- dynamic_SettingClearSecretsWithFlagsFn :: (HasCallStack, MonadIO m, IsSetting a) => FunPtr C_SettingClearSecretsWithFlagsFn -> a -> Text -> [SettingSecretFlags] -> Ptr () -> m Bool
- genClosure_SettingClearSecretsWithFlagsFn :: MonadIO m => SettingClearSecretsWithFlagsFn -> m (GClosure C_SettingClearSecretsWithFlagsFn)
- mk_SettingClearSecretsWithFlagsFn :: C_SettingClearSecretsWithFlagsFn -> IO (FunPtr C_SettingClearSecretsWithFlagsFn)
- noSettingClearSecretsWithFlagsFn :: Maybe SettingClearSecretsWithFlagsFn
- noSettingClearSecretsWithFlagsFn_WithClosures :: Maybe SettingClearSecretsWithFlagsFn_WithClosures
- wrap_SettingClearSecretsWithFlagsFn :: Maybe (Ptr (FunPtr C_SettingClearSecretsWithFlagsFn)) -> SettingClearSecretsWithFlagsFn_WithClosures -> C_SettingClearSecretsWithFlagsFn
- type C_SettingValueIterFn = Ptr Setting -> CString -> Ptr GValue -> CUInt -> Ptr () -> IO ()
- type SettingValueIterFn = Setting -> Text -> GValue -> [ParamFlags] -> IO ()
- type SettingValueIterFn_WithClosures = Setting -> Text -> GValue -> [ParamFlags] -> Ptr () -> IO ()
- drop_closures_SettingValueIterFn :: SettingValueIterFn -> SettingValueIterFn_WithClosures
- dynamic_SettingValueIterFn :: (HasCallStack, MonadIO m, IsSetting a) => FunPtr C_SettingValueIterFn -> a -> Text -> GValue -> [ParamFlags] -> Ptr () -> m ()
- genClosure_SettingValueIterFn :: MonadIO m => SettingValueIterFn -> m (GClosure C_SettingValueIterFn)
- mk_SettingValueIterFn :: C_SettingValueIterFn -> IO (FunPtr C_SettingValueIterFn)
- noSettingValueIterFn :: Maybe SettingValueIterFn
- noSettingValueIterFn_WithClosures :: Maybe SettingValueIterFn_WithClosures
- wrap_SettingValueIterFn :: Maybe (Ptr (FunPtr C_SettingValueIterFn)) -> SettingValueIterFn_WithClosures -> C_SettingValueIterFn
- type C_UtilsCheckFilePredicate = CString -> Ptr () -> Ptr () -> Ptr (Ptr GError) -> IO CInt
- type UtilsCheckFilePredicate = Text -> Ptr () -> IO ()
- type UtilsCheckFilePredicate_WithClosures = Text -> Ptr () -> Ptr () -> IO ()
- drop_closures_UtilsCheckFilePredicate :: UtilsCheckFilePredicate -> UtilsCheckFilePredicate_WithClosures
- dynamic_UtilsCheckFilePredicate :: (HasCallStack, MonadIO m) => FunPtr C_UtilsCheckFilePredicate -> Text -> Ptr () -> Ptr () -> m ()
- mk_UtilsCheckFilePredicate :: C_UtilsCheckFilePredicate -> IO (FunPtr C_UtilsCheckFilePredicate)
- noUtilsCheckFilePredicate :: Maybe UtilsCheckFilePredicate
- noUtilsCheckFilePredicate_WithClosures :: Maybe UtilsCheckFilePredicate_WithClosures
- type C_UtilsFileSearchInPathsPredicate = CString -> Ptr () -> IO CInt
- type UtilsFileSearchInPathsPredicate = Text -> IO Bool
- type UtilsFileSearchInPathsPredicate_WithClosures = Text -> Ptr () -> IO Bool
- drop_closures_UtilsFileSearchInPathsPredicate :: UtilsFileSearchInPathsPredicate -> UtilsFileSearchInPathsPredicate_WithClosures
- dynamic_UtilsFileSearchInPathsPredicate :: (HasCallStack, MonadIO m) => FunPtr C_UtilsFileSearchInPathsPredicate -> Text -> Ptr () -> m Bool
- genClosure_UtilsFileSearchInPathsPredicate :: MonadIO m => UtilsFileSearchInPathsPredicate -> m (GClosure C_UtilsFileSearchInPathsPredicate)
- mk_UtilsFileSearchInPathsPredicate :: C_UtilsFileSearchInPathsPredicate -> IO (FunPtr C_UtilsFileSearchInPathsPredicate)
- noUtilsFileSearchInPathsPredicate :: Maybe UtilsFileSearchInPathsPredicate
- noUtilsFileSearchInPathsPredicate_WithClosures :: Maybe UtilsFileSearchInPathsPredicate_WithClosures
- wrap_UtilsFileSearchInPathsPredicate :: Maybe (Ptr (FunPtr C_UtilsFileSearchInPathsPredicate)) -> UtilsFileSearchInPathsPredicate_WithClosures -> C_UtilsFileSearchInPathsPredicate
- type C_UtilsPredicateStr = CString -> IO CInt
- type UtilsPredicateStr = Text -> IO Bool
- dynamic_UtilsPredicateStr :: (HasCallStack, MonadIO m) => FunPtr C_UtilsPredicateStr -> Text -> m Bool
- genClosure_UtilsPredicateStr :: MonadIO m => UtilsPredicateStr -> m (GClosure C_UtilsPredicateStr)
- mk_UtilsPredicateStr :: C_UtilsPredicateStr -> IO (FunPtr C_UtilsPredicateStr)
- noUtilsPredicateStr :: Maybe UtilsPredicateStr
- wrap_UtilsPredicateStr :: Maybe (Ptr (FunPtr C_UtilsPredicateStr)) -> UtilsPredicateStr -> C_UtilsPredicateStr
- type C_VpnIterFunc = CString -> CString -> Ptr () -> IO ()
- type VpnIterFunc = Text -> Text -> IO ()
- type VpnIterFunc_WithClosures = Text -> Text -> Ptr () -> IO ()
- drop_closures_VpnIterFunc :: VpnIterFunc -> VpnIterFunc_WithClosures
- dynamic_VpnIterFunc :: (HasCallStack, MonadIO m) => FunPtr C_VpnIterFunc -> Text -> Text -> Ptr () -> m ()
- genClosure_VpnIterFunc :: MonadIO m => VpnIterFunc -> m (GClosure C_VpnIterFunc)
- mk_VpnIterFunc :: C_VpnIterFunc -> IO (FunPtr C_VpnIterFunc)
- noVpnIterFunc :: Maybe VpnIterFunc
- noVpnIterFunc_WithClosures :: Maybe VpnIterFunc_WithClosures
- wrap_VpnIterFunc :: Maybe (Ptr (FunPtr C_VpnIterFunc)) -> VpnIterFunc_WithClosures -> C_VpnIterFunc
Signals
KeyfileReadHandler
type C_KeyfileReadHandler = Ptr KeyFile -> Ptr Connection -> CUInt -> Ptr KeyfileHandlerData -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type KeyfileReadHandler Source #
Arguments
= KeyFile |
|
-> Connection |
|
-> KeyfileHandlerType |
|
-> KeyfileHandlerData |
|
-> IO Bool | Returns: the callee should return TRUE, if the event was handled and/or recognized.
Otherwise, a default action will be performed that depends on the |
Hook to keyfileRead
.
The callee may abort the reading by setting an error via keyfileHandlerDataFailWithError
.
Since: 1.30
type KeyfileReadHandler_WithClosures Source #
Arguments
= KeyFile |
|
-> Connection |
|
-> KeyfileHandlerType |
|
-> KeyfileHandlerData |
|
-> Ptr () |
|
-> IO Bool | Returns: the callee should return TRUE, if the event was handled and/or recognized.
Otherwise, a default action will be performed that depends on the |
Hook to keyfileRead
.
The callee may abort the reading by setting an error via keyfileHandlerDataFailWithError
.
Since: 1.30
drop_closures_KeyfileReadHandler :: KeyfileReadHandler -> KeyfileReadHandler_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_KeyfileReadHandler Source #
Arguments
:: (HasCallStack, MonadIO m, IsConnection a) | |
=> FunPtr C_KeyfileReadHandler | |
-> KeyFile |
|
-> a |
|
-> KeyfileHandlerType |
|
-> KeyfileHandlerData |
|
-> Ptr () |
|
-> m Bool | Returns: the callee should return TRUE, if the event was handled and/or recognized.
Otherwise, a default action will be performed that depends on the |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_KeyfileReadHandler :: MonadIO m => KeyfileReadHandler -> m (GClosure C_KeyfileReadHandler) Source #
Wrap the callback into a GClosure
.
mk_KeyfileReadHandler :: C_KeyfileReadHandler -> IO (FunPtr C_KeyfileReadHandler) Source #
Generate a function pointer callable from C code, from a C_KeyfileReadHandler
.
noKeyfileReadHandler :: Maybe KeyfileReadHandler Source #
A convenience synonym for
.Nothing
:: Maybe
KeyfileReadHandler
noKeyfileReadHandler_WithClosures :: Maybe KeyfileReadHandler_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
KeyfileReadHandler_WithClosures
wrap_KeyfileReadHandler :: Maybe (Ptr (FunPtr C_KeyfileReadHandler)) -> KeyfileReadHandler_WithClosures -> C_KeyfileReadHandler Source #
Wrap a KeyfileReadHandler
into a C_KeyfileReadHandler
.
KeyfileWriteHandler
type C_KeyfileWriteHandler = Ptr Connection -> Ptr KeyFile -> CUInt -> Ptr KeyfileHandlerData -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type KeyfileWriteHandler Source #
Arguments
= Connection |
|
-> KeyFile |
|
-> KeyfileHandlerType |
|
-> KeyfileHandlerData |
|
-> IO Bool | Returns: the callee should return |
This is a hook to tweak the serialization.
Handler for certain properties or events that are not entirely contained
within the keyfile or that might be serialized differently. The type
and
handlerData
arguments tell which kind of argument we have at hand.
Currently only the type KeyfileHandlerTypeWriteCert
is supported.
The callee may call keyfileHandlerDataFailWithError
to abort
the writing with error.
Since: 1.30
type KeyfileWriteHandler_WithClosures Source #
Arguments
= Connection |
|
-> KeyFile |
|
-> KeyfileHandlerType |
|
-> KeyfileHandlerData |
|
-> Ptr () |
|
-> IO Bool | Returns: the callee should return |
This is a hook to tweak the serialization.
Handler for certain properties or events that are not entirely contained
within the keyfile or that might be serialized differently. The type
and
handlerData
arguments tell which kind of argument we have at hand.
Currently only the type KeyfileHandlerTypeWriteCert
is supported.
The callee may call keyfileHandlerDataFailWithError
to abort
the writing with error.
Since: 1.30
drop_closures_KeyfileWriteHandler :: KeyfileWriteHandler -> KeyfileWriteHandler_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_KeyfileWriteHandler Source #
Arguments
:: (HasCallStack, MonadIO m, IsConnection a) | |
=> FunPtr C_KeyfileWriteHandler | |
-> a |
|
-> KeyFile |
|
-> KeyfileHandlerType |
|
-> KeyfileHandlerData |
|
-> Ptr () |
|
-> m Bool | Returns: the callee should return |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_KeyfileWriteHandler :: MonadIO m => KeyfileWriteHandler -> m (GClosure C_KeyfileWriteHandler) Source #
Wrap the callback into a GClosure
.
mk_KeyfileWriteHandler :: C_KeyfileWriteHandler -> IO (FunPtr C_KeyfileWriteHandler) Source #
Generate a function pointer callable from C code, from a C_KeyfileWriteHandler
.
noKeyfileWriteHandler :: Maybe KeyfileWriteHandler Source #
A convenience synonym for
.Nothing
:: Maybe
KeyfileWriteHandler
noKeyfileWriteHandler_WithClosures :: Maybe KeyfileWriteHandler_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
KeyfileWriteHandler_WithClosures
wrap_KeyfileWriteHandler :: Maybe (Ptr (FunPtr C_KeyfileWriteHandler)) -> KeyfileWriteHandler_WithClosures -> C_KeyfileWriteHandler Source #
Wrap a KeyfileWriteHandler
into a C_KeyfileWriteHandler
.
SecretAgentOldDeleteSecretsFunc
type C_SecretAgentOldDeleteSecretsFunc = Ptr SecretAgentOld -> Ptr Connection -> Ptr GError -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SecretAgentOldDeleteSecretsFunc Source #
Arguments
= SecretAgentOld |
|
-> Connection |
|
-> GError |
|
-> IO () |
Called as a result of a request by NM to delete secrets. When the
SecretAgentOld
subclass has finished deleting the secrets, this function
should be called.
type SecretAgentOldDeleteSecretsFunc_WithClosures Source #
Arguments
= SecretAgentOld |
|
-> Connection |
|
-> GError |
|
-> Ptr () |
|
-> IO () |
Called as a result of a request by NM to delete secrets. When the
SecretAgentOld
subclass has finished deleting the secrets, this function
should be called.
drop_closures_SecretAgentOldDeleteSecretsFunc :: SecretAgentOldDeleteSecretsFunc -> SecretAgentOldDeleteSecretsFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SecretAgentOldDeleteSecretsFunc Source #
Arguments
:: (HasCallStack, MonadIO m, IsSecretAgentOld a, IsConnection b) | |
=> FunPtr C_SecretAgentOldDeleteSecretsFunc | |
-> a |
|
-> b |
|
-> GError |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SecretAgentOldDeleteSecretsFunc :: MonadIO m => SecretAgentOldDeleteSecretsFunc -> m (GClosure C_SecretAgentOldDeleteSecretsFunc) Source #
Wrap the callback into a GClosure
.
mk_SecretAgentOldDeleteSecretsFunc :: C_SecretAgentOldDeleteSecretsFunc -> IO (FunPtr C_SecretAgentOldDeleteSecretsFunc) Source #
Generate a function pointer callable from C code, from a C_SecretAgentOldDeleteSecretsFunc
.
noSecretAgentOldDeleteSecretsFunc :: Maybe SecretAgentOldDeleteSecretsFunc Source #
A convenience synonym for
.Nothing
:: Maybe
SecretAgentOldDeleteSecretsFunc
noSecretAgentOldDeleteSecretsFunc_WithClosures :: Maybe SecretAgentOldDeleteSecretsFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SecretAgentOldDeleteSecretsFunc_WithClosures
wrap_SecretAgentOldDeleteSecretsFunc :: Maybe (Ptr (FunPtr C_SecretAgentOldDeleteSecretsFunc)) -> SecretAgentOldDeleteSecretsFunc_WithClosures -> C_SecretAgentOldDeleteSecretsFunc Source #
Wrap a SecretAgentOldDeleteSecretsFunc
into a C_SecretAgentOldDeleteSecretsFunc
.
SecretAgentOldGetSecretsFunc
type C_SecretAgentOldGetSecretsFunc = Ptr SecretAgentOld -> Ptr Connection -> Ptr GVariant -> Ptr GError -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SecretAgentOldGetSecretsFunc Source #
Arguments
= SecretAgentOld |
|
-> Connection |
|
-> GVariant |
|
-> GError |
|
-> IO () |
Called as a result of a request by NM to retrieve secrets. When the
SecretAgentOld
subclass has finished retrieving secrets and is ready to
return them, or to return an error, this function should be called with
those secrets or the error.
To easily create the dictionary to return the Wi-Fi PSK, you could do something like this: <example> <title>Creating a secrets dictionary</title> <programlisting> NMConnection *secrets; NMSettingWirelessSecurity *s_wsec; GVariant *secrets_dict;
secrets = nm_simple_connection_new (); s_wsec = (NMSettingWirelessSecurity *) nm_setting_wireless_security_new (); g_object_set (G_OBJECT (s_wsec), NM_SETTING_WIRELESS_SECURITY_PSK, "my really cool PSK", NULL); nm_connection_add_setting (secrets, NM_SETTING (s_wsec)); secrets_dict = nm_connection_to_dbus (secrets, NM_CONNECTION_SERIALIZE_ALL);
(call the NMSecretAgentOldGetSecretsFunc with secrets_dict)
g_object_unref (secrets); g_variant_unref (secrets_dict); </programlisting> </example>
type SecretAgentOldGetSecretsFunc_WithClosures Source #
Arguments
= SecretAgentOld |
|
-> Connection |
|
-> GVariant |
|
-> GError |
|
-> Ptr () |
|
-> IO () |
Called as a result of a request by NM to retrieve secrets. When the
SecretAgentOld
subclass has finished retrieving secrets and is ready to
return them, or to return an error, this function should be called with
those secrets or the error.
To easily create the dictionary to return the Wi-Fi PSK, you could do something like this: <example> <title>Creating a secrets dictionary</title> <programlisting> NMConnection *secrets; NMSettingWirelessSecurity *s_wsec; GVariant *secrets_dict;
secrets = nm_simple_connection_new (); s_wsec = (NMSettingWirelessSecurity *) nm_setting_wireless_security_new (); g_object_set (G_OBJECT (s_wsec), NM_SETTING_WIRELESS_SECURITY_PSK, "my really cool PSK", NULL); nm_connection_add_setting (secrets, NM_SETTING (s_wsec)); secrets_dict = nm_connection_to_dbus (secrets, NM_CONNECTION_SERIALIZE_ALL);
(call the NMSecretAgentOldGetSecretsFunc with secrets_dict)
g_object_unref (secrets); g_variant_unref (secrets_dict); </programlisting> </example>
drop_closures_SecretAgentOldGetSecretsFunc :: SecretAgentOldGetSecretsFunc -> SecretAgentOldGetSecretsFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SecretAgentOldGetSecretsFunc Source #
Arguments
:: (HasCallStack, MonadIO m, IsSecretAgentOld a, IsConnection b) | |
=> FunPtr C_SecretAgentOldGetSecretsFunc | |
-> a |
|
-> b |
|
-> GVariant |
|
-> GError |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SecretAgentOldGetSecretsFunc :: MonadIO m => SecretAgentOldGetSecretsFunc -> m (GClosure C_SecretAgentOldGetSecretsFunc) Source #
Wrap the callback into a GClosure
.
mk_SecretAgentOldGetSecretsFunc :: C_SecretAgentOldGetSecretsFunc -> IO (FunPtr C_SecretAgentOldGetSecretsFunc) Source #
Generate a function pointer callable from C code, from a C_SecretAgentOldGetSecretsFunc
.
noSecretAgentOldGetSecretsFunc :: Maybe SecretAgentOldGetSecretsFunc Source #
A convenience synonym for
.Nothing
:: Maybe
SecretAgentOldGetSecretsFunc
noSecretAgentOldGetSecretsFunc_WithClosures :: Maybe SecretAgentOldGetSecretsFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SecretAgentOldGetSecretsFunc_WithClosures
wrap_SecretAgentOldGetSecretsFunc :: Maybe (Ptr (FunPtr C_SecretAgentOldGetSecretsFunc)) -> SecretAgentOldGetSecretsFunc_WithClosures -> C_SecretAgentOldGetSecretsFunc Source #
Wrap a SecretAgentOldGetSecretsFunc
into a C_SecretAgentOldGetSecretsFunc
.
SecretAgentOldSaveSecretsFunc
type C_SecretAgentOldSaveSecretsFunc = Ptr SecretAgentOld -> Ptr Connection -> Ptr GError -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SecretAgentOldSaveSecretsFunc Source #
Arguments
= SecretAgentOld |
|
-> Connection |
|
-> GError |
|
-> IO () |
Called as a result of a request by NM to save secrets. When the
SecretAgentOld
subclass has finished saving the secrets, this function
should be called.
type SecretAgentOldSaveSecretsFunc_WithClosures Source #
Arguments
= SecretAgentOld |
|
-> Connection |
|
-> GError |
|
-> Ptr () |
|
-> IO () |
Called as a result of a request by NM to save secrets. When the
SecretAgentOld
subclass has finished saving the secrets, this function
should be called.
drop_closures_SecretAgentOldSaveSecretsFunc :: SecretAgentOldSaveSecretsFunc -> SecretAgentOldSaveSecretsFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SecretAgentOldSaveSecretsFunc Source #
Arguments
:: (HasCallStack, MonadIO m, IsSecretAgentOld a, IsConnection b) | |
=> FunPtr C_SecretAgentOldSaveSecretsFunc | |
-> a |
|
-> b |
|
-> GError |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SecretAgentOldSaveSecretsFunc :: MonadIO m => SecretAgentOldSaveSecretsFunc -> m (GClosure C_SecretAgentOldSaveSecretsFunc) Source #
Wrap the callback into a GClosure
.
mk_SecretAgentOldSaveSecretsFunc :: C_SecretAgentOldSaveSecretsFunc -> IO (FunPtr C_SecretAgentOldSaveSecretsFunc) Source #
Generate a function pointer callable from C code, from a C_SecretAgentOldSaveSecretsFunc
.
noSecretAgentOldSaveSecretsFunc :: Maybe SecretAgentOldSaveSecretsFunc Source #
A convenience synonym for
.Nothing
:: Maybe
SecretAgentOldSaveSecretsFunc
noSecretAgentOldSaveSecretsFunc_WithClosures :: Maybe SecretAgentOldSaveSecretsFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SecretAgentOldSaveSecretsFunc_WithClosures
wrap_SecretAgentOldSaveSecretsFunc :: Maybe (Ptr (FunPtr C_SecretAgentOldSaveSecretsFunc)) -> SecretAgentOldSaveSecretsFunc_WithClosures -> C_SecretAgentOldSaveSecretsFunc Source #
Wrap a SecretAgentOldSaveSecretsFunc
into a C_SecretAgentOldSaveSecretsFunc
.
SettingClearSecretsWithFlagsFn
type C_SettingClearSecretsWithFlagsFn = Ptr Setting -> CString -> CUInt -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type SettingClearSecretsWithFlagsFn Source #
Arguments
= Setting |
|
-> Text |
|
-> [SettingSecretFlags] |
|
-> IO Bool | Returns: |
No description available in the introspection data.
type SettingClearSecretsWithFlagsFn_WithClosures Source #
Arguments
= Setting |
|
-> Text |
|
-> [SettingSecretFlags] |
|
-> Ptr () |
|
-> IO Bool | Returns: |
No description available in the introspection data.
drop_closures_SettingClearSecretsWithFlagsFn :: SettingClearSecretsWithFlagsFn -> SettingClearSecretsWithFlagsFn_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SettingClearSecretsWithFlagsFn Source #
Arguments
:: (HasCallStack, MonadIO m, IsSetting a) | |
=> FunPtr C_SettingClearSecretsWithFlagsFn | |
-> a |
|
-> Text |
|
-> [SettingSecretFlags] |
|
-> Ptr () |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SettingClearSecretsWithFlagsFn :: MonadIO m => SettingClearSecretsWithFlagsFn -> m (GClosure C_SettingClearSecretsWithFlagsFn) Source #
Wrap the callback into a GClosure
.
mk_SettingClearSecretsWithFlagsFn :: C_SettingClearSecretsWithFlagsFn -> IO (FunPtr C_SettingClearSecretsWithFlagsFn) Source #
Generate a function pointer callable from C code, from a C_SettingClearSecretsWithFlagsFn
.
noSettingClearSecretsWithFlagsFn :: Maybe SettingClearSecretsWithFlagsFn Source #
A convenience synonym for
.Nothing
:: Maybe
SettingClearSecretsWithFlagsFn
noSettingClearSecretsWithFlagsFn_WithClosures :: Maybe SettingClearSecretsWithFlagsFn_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SettingClearSecretsWithFlagsFn_WithClosures
wrap_SettingClearSecretsWithFlagsFn :: Maybe (Ptr (FunPtr C_SettingClearSecretsWithFlagsFn)) -> SettingClearSecretsWithFlagsFn_WithClosures -> C_SettingClearSecretsWithFlagsFn Source #
Wrap a SettingClearSecretsWithFlagsFn
into a C_SettingClearSecretsWithFlagsFn
.
SettingValueIterFn
type C_SettingValueIterFn = Ptr Setting -> CString -> Ptr GValue -> CUInt -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type SettingValueIterFn Source #
Arguments
= Setting |
|
-> Text |
|
-> GValue |
|
-> [ParamFlags] |
|
-> IO () |
No description available in the introspection data.
type SettingValueIterFn_WithClosures Source #
Arguments
= Setting |
|
-> Text |
|
-> GValue |
|
-> [ParamFlags] |
|
-> Ptr () |
|
-> IO () |
No description available in the introspection data.
drop_closures_SettingValueIterFn :: SettingValueIterFn -> SettingValueIterFn_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_SettingValueIterFn Source #
Arguments
:: (HasCallStack, MonadIO m, IsSetting a) | |
=> FunPtr C_SettingValueIterFn | |
-> a |
|
-> Text |
|
-> GValue |
|
-> [ParamFlags] |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_SettingValueIterFn :: MonadIO m => SettingValueIterFn -> m (GClosure C_SettingValueIterFn) Source #
Wrap the callback into a GClosure
.
mk_SettingValueIterFn :: C_SettingValueIterFn -> IO (FunPtr C_SettingValueIterFn) Source #
Generate a function pointer callable from C code, from a C_SettingValueIterFn
.
noSettingValueIterFn :: Maybe SettingValueIterFn Source #
A convenience synonym for
.Nothing
:: Maybe
SettingValueIterFn
noSettingValueIterFn_WithClosures :: Maybe SettingValueIterFn_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
SettingValueIterFn_WithClosures
wrap_SettingValueIterFn :: Maybe (Ptr (FunPtr C_SettingValueIterFn)) -> SettingValueIterFn_WithClosures -> C_SettingValueIterFn Source #
Wrap a SettingValueIterFn
into a C_SettingValueIterFn
.
UtilsCheckFilePredicate
type C_UtilsCheckFilePredicate = CString -> Ptr () -> Ptr () -> Ptr (Ptr GError) -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type UtilsCheckFilePredicate Source #
No description available in the introspection data.
type UtilsCheckFilePredicate_WithClosures Source #
No description available in the introspection data.
drop_closures_UtilsCheckFilePredicate :: UtilsCheckFilePredicate -> UtilsCheckFilePredicate_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UtilsCheckFilePredicate Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UtilsCheckFilePredicate | |
-> Text | |
-> Ptr () | |
-> Ptr () | |
-> m () | (Can throw |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
mk_UtilsCheckFilePredicate :: C_UtilsCheckFilePredicate -> IO (FunPtr C_UtilsCheckFilePredicate) Source #
Generate a function pointer callable from C code, from a C_UtilsCheckFilePredicate
.
noUtilsCheckFilePredicate :: Maybe UtilsCheckFilePredicate Source #
A convenience synonym for
.Nothing
:: Maybe
UtilsCheckFilePredicate
noUtilsCheckFilePredicate_WithClosures :: Maybe UtilsCheckFilePredicate_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UtilsCheckFilePredicate_WithClosures
UtilsFileSearchInPathsPredicate
type C_UtilsFileSearchInPathsPredicate = CString -> Ptr () -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type UtilsFileSearchInPathsPredicate = Text -> IO Bool Source #
No description available in the introspection data.
type UtilsFileSearchInPathsPredicate_WithClosures = Text -> Ptr () -> IO Bool Source #
No description available in the introspection data.
drop_closures_UtilsFileSearchInPathsPredicate :: UtilsFileSearchInPathsPredicate -> UtilsFileSearchInPathsPredicate_WithClosures Source #
A simple wrapper that ignores the closure arguments.
dynamic_UtilsFileSearchInPathsPredicate :: (HasCallStack, MonadIO m) => FunPtr C_UtilsFileSearchInPathsPredicate -> Text -> Ptr () -> m Bool Source #
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UtilsFileSearchInPathsPredicate :: MonadIO m => UtilsFileSearchInPathsPredicate -> m (GClosure C_UtilsFileSearchInPathsPredicate) Source #
Wrap the callback into a GClosure
.
mk_UtilsFileSearchInPathsPredicate :: C_UtilsFileSearchInPathsPredicate -> IO (FunPtr C_UtilsFileSearchInPathsPredicate) Source #
Generate a function pointer callable from C code, from a C_UtilsFileSearchInPathsPredicate
.
noUtilsFileSearchInPathsPredicate :: Maybe UtilsFileSearchInPathsPredicate Source #
A convenience synonym for
.Nothing
:: Maybe
UtilsFileSearchInPathsPredicate
noUtilsFileSearchInPathsPredicate_WithClosures :: Maybe UtilsFileSearchInPathsPredicate_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
UtilsFileSearchInPathsPredicate_WithClosures
wrap_UtilsFileSearchInPathsPredicate :: Maybe (Ptr (FunPtr C_UtilsFileSearchInPathsPredicate)) -> UtilsFileSearchInPathsPredicate_WithClosures -> C_UtilsFileSearchInPathsPredicate Source #
Wrap a UtilsFileSearchInPathsPredicate
into a C_UtilsFileSearchInPathsPredicate
.
UtilsPredicateStr
type C_UtilsPredicateStr = CString -> IO CInt Source #
Type for the callback on the (unwrapped) C side.
type UtilsPredicateStr Source #
This function takes a string argument and returns either True
or False
.
It is a general purpose predicate, for example used by settingOptionClearByName
.
Since: 1.26
dynamic_UtilsPredicateStr Source #
Arguments
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_UtilsPredicateStr | |
-> Text |
|
-> m Bool | Returns: |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_UtilsPredicateStr :: MonadIO m => UtilsPredicateStr -> m (GClosure C_UtilsPredicateStr) Source #
Wrap the callback into a GClosure
.
mk_UtilsPredicateStr :: C_UtilsPredicateStr -> IO (FunPtr C_UtilsPredicateStr) Source #
Generate a function pointer callable from C code, from a C_UtilsPredicateStr
.
noUtilsPredicateStr :: Maybe UtilsPredicateStr Source #
A convenience synonym for
.Nothing
:: Maybe
UtilsPredicateStr
wrap_UtilsPredicateStr :: Maybe (Ptr (FunPtr C_UtilsPredicateStr)) -> UtilsPredicateStr -> C_UtilsPredicateStr Source #
Wrap a UtilsPredicateStr
into a C_UtilsPredicateStr
.
VpnIterFunc
type C_VpnIterFunc = CString -> CString -> Ptr () -> IO () Source #
Type for the callback on the (unwrapped) C side.
type VpnIterFunc Source #
Arguments
= Text |
|
-> Text |
|
-> IO () |
No description available in the introspection data.
type VpnIterFunc_WithClosures Source #
Arguments
= Text |
|
-> Text |
|
-> Ptr () |
|
-> IO () |
No description available in the introspection data.
drop_closures_VpnIterFunc :: VpnIterFunc -> VpnIterFunc_WithClosures Source #
A simple wrapper that ignores the closure arguments.
Arguments
:: (HasCallStack, MonadIO m) | |
=> FunPtr C_VpnIterFunc | |
-> Text |
|
-> Text |
|
-> Ptr () |
|
-> m () |
Given a pointer to a foreign C function, wrap it into a function callable from Haskell.
genClosure_VpnIterFunc :: MonadIO m => VpnIterFunc -> m (GClosure C_VpnIterFunc) Source #
Wrap the callback into a GClosure
.
mk_VpnIterFunc :: C_VpnIterFunc -> IO (FunPtr C_VpnIterFunc) Source #
Generate a function pointer callable from C code, from a C_VpnIterFunc
.
noVpnIterFunc :: Maybe VpnIterFunc Source #
A convenience synonym for
.Nothing
:: Maybe
VpnIterFunc
noVpnIterFunc_WithClosures :: Maybe VpnIterFunc_WithClosures Source #
A convenience synonym for
.Nothing
:: Maybe
VpnIterFunc_WithClosures
wrap_VpnIterFunc :: Maybe (Ptr (FunPtr C_VpnIterFunc)) -> VpnIterFunc_WithClosures -> C_VpnIterFunc Source #
Wrap a VpnIterFunc
into a C_VpnIterFunc
.