{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Secret.Interfaces.Retrievable
(
Retrievable(..) ,
IsRetrievable ,
toRetrievable ,
#if defined(ENABLE_OVERLOADING)
ResolveRetrievableMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
RetrievableGetAttributesMethodInfo ,
#endif
retrievableGetAttributes ,
#if defined(ENABLE_OVERLOADING)
RetrievableGetCreatedMethodInfo ,
#endif
retrievableGetCreated ,
#if defined(ENABLE_OVERLOADING)
RetrievableGetLabelMethodInfo ,
#endif
retrievableGetLabel ,
#if defined(ENABLE_OVERLOADING)
RetrievableGetModifiedMethodInfo ,
#endif
retrievableGetModified ,
#if defined(ENABLE_OVERLOADING)
RetrievableRetrieveSecretMethodInfo ,
#endif
retrievableRetrieveSecret ,
#if defined(ENABLE_OVERLOADING)
RetrievableRetrieveSecretFinishMethodInfo,
#endif
retrievableRetrieveSecretFinish ,
#if defined(ENABLE_OVERLOADING)
RetrievableRetrieveSecretSyncMethodInfo ,
#endif
retrievableRetrieveSecretSync ,
#if defined(ENABLE_OVERLOADING)
RetrievableAttributesPropertyInfo ,
#endif
#if defined(ENABLE_OVERLOADING)
retrievableAttributes ,
#endif
#if defined(ENABLE_OVERLOADING)
RetrievableCreatedPropertyInfo ,
#endif
constructRetrievableCreated ,
getRetrievableCreated ,
#if defined(ENABLE_OVERLOADING)
retrievableCreated ,
#endif
setRetrievableCreated ,
#if defined(ENABLE_OVERLOADING)
RetrievableLabelPropertyInfo ,
#endif
clearRetrievableLabel ,
constructRetrievableLabel ,
getRetrievableLabel ,
#if defined(ENABLE_OVERLOADING)
retrievableLabel ,
#endif
setRetrievableLabel ,
#if defined(ENABLE_OVERLOADING)
RetrievableModifiedPropertyInfo ,
#endif
constructRetrievableModified ,
getRetrievableModified ,
#if defined(ENABLE_OVERLOADING)
retrievableModified ,
#endif
setRetrievableModified ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Secret.Structs.Value as Secret.Value
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import {-# SOURCE #-} qualified GI.Secret.Structs.Value as Secret.Value
#endif
newtype Retrievable = Retrievable (SP.ManagedPtr Retrievable)
deriving (Retrievable -> Retrievable -> Bool
(Retrievable -> Retrievable -> Bool)
-> (Retrievable -> Retrievable -> Bool) -> Eq Retrievable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Retrievable -> Retrievable -> Bool
== :: Retrievable -> Retrievable -> Bool
$c/= :: Retrievable -> Retrievable -> Bool
/= :: Retrievable -> Retrievable -> Bool
Eq)
instance SP.ManagedPtrNewtype Retrievable where
toManagedPtr :: Retrievable -> ManagedPtr Retrievable
toManagedPtr (Retrievable ManagedPtr Retrievable
p) = ManagedPtr Retrievable
p
foreign import ccall "secret_retrievable_get_type"
c_secret_retrievable_get_type :: IO B.Types.GType
instance B.Types.TypedObject Retrievable where
glibType :: IO GType
glibType = IO GType
c_secret_retrievable_get_type
instance B.Types.GObject Retrievable
class (SP.GObject o, O.IsDescendantOf Retrievable o) => IsRetrievable o
instance (SP.GObject o, O.IsDescendantOf Retrievable o) => IsRetrievable o
instance O.HasParentTypes Retrievable
type instance O.ParentTypes Retrievable = '[GObject.Object.Object]
toRetrievable :: (MIO.MonadIO m, IsRetrievable o) => o -> m Retrievable
toRetrievable :: forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> m Retrievable
toRetrievable = IO Retrievable -> m Retrievable
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Retrievable -> m Retrievable)
-> (o -> IO Retrievable) -> o -> m Retrievable
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Retrievable -> Retrievable) -> o -> IO Retrievable
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Retrievable -> Retrievable
Retrievable
instance B.GValue.IsGValue (Maybe Retrievable) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_secret_retrievable_get_type
gvalueSet_ :: Ptr GValue -> Maybe Retrievable -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Retrievable
P.Nothing = Ptr GValue -> Ptr Retrievable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Retrievable
forall a. Ptr a
FP.nullPtr :: FP.Ptr Retrievable)
gvalueSet_ Ptr GValue
gv (P.Just Retrievable
obj) = Retrievable -> (Ptr Retrievable -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Retrievable
obj (Ptr GValue -> Ptr Retrievable -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Retrievable)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr Retrievable)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Retrievable)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject Retrievable ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
data RetrievableAttributesPropertyInfo
instance AttrInfo RetrievableAttributesPropertyInfo where
type AttrAllowedOps RetrievableAttributesPropertyInfo = '[]
type AttrSetTypeConstraint RetrievableAttributesPropertyInfo = (~) ()
type AttrTransferTypeConstraint RetrievableAttributesPropertyInfo = (~) ()
type AttrTransferType RetrievableAttributesPropertyInfo = ()
type AttrBaseTypeConstraint RetrievableAttributesPropertyInfo = (~) ()
type AttrGetType RetrievableAttributesPropertyInfo = ()
type AttrLabel RetrievableAttributesPropertyInfo = ""
type AttrOrigin RetrievableAttributesPropertyInfo = Retrievable
attrGet :: forall o.
AttrBaseTypeConstraint RetrievableAttributesPropertyInfo o =>
o -> IO (AttrGetType RetrievableAttributesPropertyInfo)
attrGet = o -> IO (AttrGetType RetrievableAttributesPropertyInfo)
() -> IO ()
forall a. HasCallStack => a
undefined
attrSet :: forall o b.
(AttrBaseTypeConstraint RetrievableAttributesPropertyInfo o,
AttrSetTypeConstraint RetrievableAttributesPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
forall a. HasCallStack => a
undefined
attrConstruct :: forall o b.
(AttrBaseTypeConstraint RetrievableAttributesPropertyInfo o,
AttrSetTypeConstraint RetrievableAttributesPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
forall a. HasCallStack => a
undefined
attrClear :: forall o.
AttrBaseTypeConstraint RetrievableAttributesPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
attrTransfer :: forall o b.
(AttrBaseTypeConstraint RetrievableAttributesPropertyInfo o,
AttrTransferTypeConstraint RetrievableAttributesPropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType RetrievableAttributesPropertyInfo)
attrTransfer = Proxy o
-> b -> IO (AttrTransferType RetrievableAttributesPropertyInfo)
Proxy () -> () -> IO ()
forall a. HasCallStack => a
undefined
#endif
getRetrievableCreated :: (MonadIO m, IsRetrievable o) => o -> m Word64
getRetrievableCreated :: forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> m Word64
getRetrievableCreated o
obj = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word64
forall a. GObject a => a -> String -> IO Word64
B.Properties.getObjectPropertyUInt64 o
obj String
"created"
setRetrievableCreated :: (MonadIO m, IsRetrievable o) => o -> Word64 -> m ()
setRetrievableCreated :: forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> Word64 -> m ()
setRetrievableCreated o
obj Word64
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Word64 -> IO ()
forall a. GObject a => a -> String -> Word64 -> IO ()
B.Properties.setObjectPropertyUInt64 o
obj String
"created" Word64
val
constructRetrievableCreated :: (IsRetrievable o, MIO.MonadIO m) => Word64 -> m (GValueConstruct o)
constructRetrievableCreated :: forall o (m :: * -> *).
(IsRetrievable o, MonadIO m) =>
Word64 -> m (GValueConstruct o)
constructRetrievableCreated Word64
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word64 -> IO (GValueConstruct o)
forall o. String -> Word64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt64 String
"created" Word64
val
#if defined(ENABLE_OVERLOADING)
data RetrievableCreatedPropertyInfo
instance AttrInfo RetrievableCreatedPropertyInfo where
type AttrAllowedOps RetrievableCreatedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint RetrievableCreatedPropertyInfo = IsRetrievable
type AttrSetTypeConstraint RetrievableCreatedPropertyInfo = (~) Word64
type AttrTransferTypeConstraint RetrievableCreatedPropertyInfo = (~) Word64
type AttrTransferType RetrievableCreatedPropertyInfo = Word64
type AttrGetType RetrievableCreatedPropertyInfo = Word64
type AttrLabel RetrievableCreatedPropertyInfo = "created"
type AttrOrigin RetrievableCreatedPropertyInfo = Retrievable
attrGet :: forall o.
AttrBaseTypeConstraint RetrievableCreatedPropertyInfo o =>
o -> IO (AttrGetType RetrievableCreatedPropertyInfo)
attrGet = o -> IO Word64
o -> IO (AttrGetType RetrievableCreatedPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> m Word64
getRetrievableCreated
attrSet :: forall o b.
(AttrBaseTypeConstraint RetrievableCreatedPropertyInfo o,
AttrSetTypeConstraint RetrievableCreatedPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
o -> Word64 -> IO ()
forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> Word64 -> m ()
setRetrievableCreated
attrTransfer :: forall o b.
(AttrBaseTypeConstraint RetrievableCreatedPropertyInfo o,
AttrTransferTypeConstraint RetrievableCreatedPropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType RetrievableCreatedPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint RetrievableCreatedPropertyInfo o,
AttrSetTypeConstraint RetrievableCreatedPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Word64 -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsRetrievable o, MonadIO m) =>
Word64 -> m (GValueConstruct o)
constructRetrievableCreated
attrClear :: forall o.
AttrBaseTypeConstraint RetrievableCreatedPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.created"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#g:attr:created"
})
#endif
getRetrievableLabel :: (MonadIO m, IsRetrievable o) => o -> m (Maybe T.Text)
getRetrievableLabel :: forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> m (Maybe Text)
getRetrievableLabel o
obj = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"label"
setRetrievableLabel :: (MonadIO m, IsRetrievable o) => o -> T.Text -> m ()
setRetrievableLabel :: forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> Text -> m ()
setRetrievableLabel o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructRetrievableLabel :: (IsRetrievable o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructRetrievableLabel :: forall o (m :: * -> *).
(IsRetrievable o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructRetrievableLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearRetrievableLabel :: (MonadIO m, IsRetrievable o) => o -> m ()
clearRetrievableLabel :: forall (m :: * -> *) o. (MonadIO m, IsRetrievable o) => o -> m ()
clearRetrievableLabel o
obj = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"label" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data RetrievableLabelPropertyInfo
instance AttrInfo RetrievableLabelPropertyInfo where
type AttrAllowedOps RetrievableLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint RetrievableLabelPropertyInfo = IsRetrievable
type AttrSetTypeConstraint RetrievableLabelPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint RetrievableLabelPropertyInfo = (~) T.Text
type AttrTransferType RetrievableLabelPropertyInfo = T.Text
type AttrGetType RetrievableLabelPropertyInfo = (Maybe T.Text)
type AttrLabel RetrievableLabelPropertyInfo = "label"
type AttrOrigin RetrievableLabelPropertyInfo = Retrievable
attrGet :: forall o.
AttrBaseTypeConstraint RetrievableLabelPropertyInfo o =>
o -> IO (AttrGetType RetrievableLabelPropertyInfo)
attrGet = o -> IO (Maybe Text)
o -> IO (AttrGetType RetrievableLabelPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> m (Maybe Text)
getRetrievableLabel
attrSet :: forall o b.
(AttrBaseTypeConstraint RetrievableLabelPropertyInfo o,
AttrSetTypeConstraint RetrievableLabelPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
o -> Text -> IO ()
forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> Text -> m ()
setRetrievableLabel
attrTransfer :: forall o b.
(AttrBaseTypeConstraint RetrievableLabelPropertyInfo o,
AttrTransferTypeConstraint RetrievableLabelPropertyInfo b) =>
Proxy o -> b -> IO (AttrTransferType RetrievableLabelPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint RetrievableLabelPropertyInfo o,
AttrSetTypeConstraint RetrievableLabelPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Text -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsRetrievable o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructRetrievableLabel
attrClear :: forall o.
AttrBaseTypeConstraint RetrievableLabelPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall (m :: * -> *) o. (MonadIO m, IsRetrievable o) => o -> m ()
clearRetrievableLabel
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.label"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#g:attr:label"
})
#endif
getRetrievableModified :: (MonadIO m, IsRetrievable o) => o -> m Word64
getRetrievableModified :: forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> m Word64
getRetrievableModified o
obj = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Word64
forall a. GObject a => a -> String -> IO Word64
B.Properties.getObjectPropertyUInt64 o
obj String
"modified"
setRetrievableModified :: (MonadIO m, IsRetrievable o) => o -> Word64 -> m ()
setRetrievableModified :: forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> Word64 -> m ()
setRetrievableModified o
obj Word64
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
o -> String -> Word64 -> IO ()
forall a. GObject a => a -> String -> Word64 -> IO ()
B.Properties.setObjectPropertyUInt64 o
obj String
"modified" Word64
val
constructRetrievableModified :: (IsRetrievable o, MIO.MonadIO m) => Word64 -> m (GValueConstruct o)
constructRetrievableModified :: forall o (m :: * -> *).
(IsRetrievable o, MonadIO m) =>
Word64 -> m (GValueConstruct o)
constructRetrievableModified Word64
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Word64 -> IO (GValueConstruct o)
forall o. String -> Word64 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyUInt64 String
"modified" Word64
val
#if defined(ENABLE_OVERLOADING)
data RetrievableModifiedPropertyInfo
instance AttrInfo RetrievableModifiedPropertyInfo where
type AttrAllowedOps RetrievableModifiedPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint RetrievableModifiedPropertyInfo = IsRetrievable
type AttrSetTypeConstraint RetrievableModifiedPropertyInfo = (~) Word64
type AttrTransferTypeConstraint RetrievableModifiedPropertyInfo = (~) Word64
type AttrTransferType RetrievableModifiedPropertyInfo = Word64
type AttrGetType RetrievableModifiedPropertyInfo = Word64
type AttrLabel RetrievableModifiedPropertyInfo = "modified"
type AttrOrigin RetrievableModifiedPropertyInfo = Retrievable
attrGet :: forall o.
AttrBaseTypeConstraint RetrievableModifiedPropertyInfo o =>
o -> IO (AttrGetType RetrievableModifiedPropertyInfo)
attrGet = o -> IO Word64
o -> IO (AttrGetType RetrievableModifiedPropertyInfo)
forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> m Word64
getRetrievableModified
attrSet :: forall o b.
(AttrBaseTypeConstraint RetrievableModifiedPropertyInfo o,
AttrSetTypeConstraint RetrievableModifiedPropertyInfo b) =>
o -> b -> IO ()
attrSet = o -> b -> IO ()
o -> Word64 -> IO ()
forall (m :: * -> *) o.
(MonadIO m, IsRetrievable o) =>
o -> Word64 -> m ()
setRetrievableModified
attrTransfer :: forall o b.
(AttrBaseTypeConstraint RetrievableModifiedPropertyInfo o,
AttrTransferTypeConstraint RetrievableModifiedPropertyInfo b) =>
Proxy o
-> b -> IO (AttrTransferType RetrievableModifiedPropertyInfo)
attrTransfer Proxy o
_ b
v = do
b -> IO b
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return b
v
attrConstruct :: forall o b.
(AttrBaseTypeConstraint RetrievableModifiedPropertyInfo o,
AttrSetTypeConstraint RetrievableModifiedPropertyInfo b) =>
b -> IO (GValueConstruct o)
attrConstruct = b -> IO (GValueConstruct o)
Word64 -> IO (GValueConstruct o)
forall o (m :: * -> *).
(IsRetrievable o, MonadIO m) =>
Word64 -> m (GValueConstruct o)
constructRetrievableModified
attrClear :: forall o.
AttrBaseTypeConstraint RetrievableModifiedPropertyInfo o =>
o -> IO ()
attrClear = o -> IO ()
forall a. HasCallStack => a
undefined
dbgAttrInfo :: Maybe ResolvedSymbolInfo
dbgAttrInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.modified"
, resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#g:attr:modified"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Retrievable
type instance O.AttributeList Retrievable = RetrievableAttributeList
type RetrievableAttributeList = ('[ '("attributes", RetrievableAttributesPropertyInfo), '("created", RetrievableCreatedPropertyInfo), '("label", RetrievableLabelPropertyInfo), '("modified", RetrievableModifiedPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
retrievableAttributes :: AttrLabelProxy "attributes"
retrievableAttributes :: AttrLabelProxy "attributes"
retrievableAttributes = AttrLabelProxy "attributes"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
retrievableCreated :: AttrLabelProxy "created"
retrievableCreated :: AttrLabelProxy "created"
retrievableCreated = AttrLabelProxy "created"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
retrievableLabel :: AttrLabelProxy "label"
retrievableLabel :: AttrLabelProxy "label"
retrievableLabel = AttrLabelProxy "label"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
retrievableModified :: AttrLabelProxy "modified"
retrievableModified :: AttrLabelProxy "modified"
retrievableModified = AttrLabelProxy "modified"
forall (a :: Symbol). AttrLabelProxy a
AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveRetrievableMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveRetrievableMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveRetrievableMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveRetrievableMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveRetrievableMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveRetrievableMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveRetrievableMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveRetrievableMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveRetrievableMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveRetrievableMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveRetrievableMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveRetrievableMethod "retrieveSecret" o = RetrievableRetrieveSecretMethodInfo
ResolveRetrievableMethod "retrieveSecretFinish" o = RetrievableRetrieveSecretFinishMethodInfo
ResolveRetrievableMethod "retrieveSecretSync" o = RetrievableRetrieveSecretSyncMethodInfo
ResolveRetrievableMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveRetrievableMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveRetrievableMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveRetrievableMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveRetrievableMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveRetrievableMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveRetrievableMethod "getAttributes" o = RetrievableGetAttributesMethodInfo
ResolveRetrievableMethod "getCreated" o = RetrievableGetCreatedMethodInfo
ResolveRetrievableMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveRetrievableMethod "getLabel" o = RetrievableGetLabelMethodInfo
ResolveRetrievableMethod "getModified" o = RetrievableGetModifiedMethodInfo
ResolveRetrievableMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveRetrievableMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveRetrievableMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveRetrievableMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveRetrievableMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveRetrievableMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveRetrievableMethod t Retrievable, O.OverloadedMethod info Retrievable p) => OL.IsLabel t (Retrievable -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: Retrievable -> p
fromLabel = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveRetrievableMethod t Retrievable, O.OverloadedMethod info Retrievable p, R.HasField t Retrievable p) => R.HasField t Retrievable p where
getField :: Retrievable -> p
getField = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#endif
instance (info ~ ResolveRetrievableMethod t Retrievable, O.OverloadedMethodInfo info Retrievable) => OL.IsLabel t (O.MethodProxy info Retrievable) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: MethodProxy info Retrievable
fromLabel = MethodProxy info Retrievable
forall info obj. MethodProxy info obj
O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
foreign import ccall "secret_retrievable_get_attributes" secret_retrievable_get_attributes ::
Ptr Retrievable ->
IO (Ptr (GHashTable CString CString))
retrievableGetAttributes ::
(B.CallStack.HasCallStack, MonadIO m, IsRetrievable a) =>
a
-> m (Map.Map T.Text T.Text)
retrievableGetAttributes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m (Map Text Text)
retrievableGetAttributes a
self = IO (Map Text Text) -> m (Map Text Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Map Text Text) -> m (Map Text Text))
-> IO (Map Text Text) -> m (Map Text Text)
forall a b. (a -> b) -> a -> b
$ do
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
result <- secret_retrievable_get_attributes self'
checkUnexpectedReturnNULL "retrievableGetAttributes" result
result' <- unpackGHashTable result
let result'' = (PtrWrapped CString -> CString)
-> [(PtrWrapped CString, PtrWrapped CString)]
-> [(CString, PtrWrapped CString)]
forall a c b. (a -> c) -> [(a, b)] -> [(c, b)]
mapFirst PtrWrapped CString -> CString
B.GHT.cstringUnpackPtr [(PtrWrapped CString, PtrWrapped CString)]
result'
result''' <- mapFirstA cstringToText result''
let result'''' = (PtrWrapped CString -> CString)
-> [(Text, PtrWrapped CString)] -> [(Text, CString)]
forall b c a. (b -> c) -> [(a, b)] -> [(a, c)]
mapSecond PtrWrapped CString -> CString
B.GHT.cstringUnpackPtr [(Text, PtrWrapped CString)]
result'''
result''''' <- mapSecondA cstringToText result''''
let result'''''' = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text, Text)]
result'''''
unrefGHashTable result
touchManagedPtr self
return result''''''
#if defined(ENABLE_OVERLOADING)
data RetrievableGetAttributesMethodInfo
instance (signature ~ (m (Map.Map T.Text T.Text)), MonadIO m, IsRetrievable a) => O.OverloadedMethod RetrievableGetAttributesMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m (Map Text Text)
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m (Map Text Text)
retrievableGetAttributes
instance O.OverloadedMethodInfo RetrievableGetAttributesMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.retrievableGetAttributes",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableGetAttributes"
})
#endif
foreign import ccall "secret_retrievable_get_created" secret_retrievable_get_created ::
Ptr Retrievable ->
IO Word64
retrievableGetCreated ::
(B.CallStack.HasCallStack, MonadIO m, IsRetrievable a) =>
a
-> m Word64
retrievableGetCreated :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m Word64
retrievableGetCreated a
self = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
result <- secret_retrievable_get_created self'
touchManagedPtr self
return result
#if defined(ENABLE_OVERLOADING)
data RetrievableGetCreatedMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsRetrievable a) => O.OverloadedMethod RetrievableGetCreatedMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m Word64
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m Word64
retrievableGetCreated
instance O.OverloadedMethodInfo RetrievableGetCreatedMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.retrievableGetCreated",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableGetCreated"
})
#endif
foreign import ccall "secret_retrievable_get_label" secret_retrievable_get_label ::
Ptr Retrievable ->
IO CString
retrievableGetLabel ::
(B.CallStack.HasCallStack, MonadIO m, IsRetrievable a) =>
a
-> m T.Text
retrievableGetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m Text
retrievableGetLabel a
self = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
result <- secret_retrievable_get_label self'
checkUnexpectedReturnNULL "retrievableGetLabel" result
result' <- cstringToText result
freeMem result
touchManagedPtr self
return result'
#if defined(ENABLE_OVERLOADING)
data RetrievableGetLabelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsRetrievable a) => O.OverloadedMethod RetrievableGetLabelMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m Text
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m Text
retrievableGetLabel
instance O.OverloadedMethodInfo RetrievableGetLabelMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.retrievableGetLabel",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableGetLabel"
})
#endif
foreign import ccall "secret_retrievable_get_modified" secret_retrievable_get_modified ::
Ptr Retrievable ->
IO Word64
retrievableGetModified ::
(B.CallStack.HasCallStack, MonadIO m, IsRetrievable a) =>
a
-> m Word64
retrievableGetModified :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m Word64
retrievableGetModified a
self = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
result <- secret_retrievable_get_modified self'
touchManagedPtr self
return result
#if defined(ENABLE_OVERLOADING)
data RetrievableGetModifiedMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsRetrievable a) => O.OverloadedMethod RetrievableGetModifiedMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> m Word64
forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m Word64
retrievableGetModified
instance O.OverloadedMethodInfo RetrievableGetModifiedMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.retrievableGetModified",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableGetModified"
})
#endif
foreign import ccall "secret_retrievable_retrieve_secret" secret_retrievable_retrieve_secret ::
Ptr Retrievable ->
Ptr Gio.Cancellable.Cancellable ->
FunPtr Gio.Callbacks.C_AsyncReadyCallback ->
Ptr () ->
IO ()
retrievableRetrieveSecret ::
(B.CallStack.HasCallStack, MonadIO m, IsRetrievable a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> Maybe (Gio.Callbacks.AsyncReadyCallback)
-> m ()
retrievableRetrieveSecret :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRetrievable a, IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
retrievableRetrieveSecret a
self Maybe b
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
maybeCancellable <- case cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
Just b
jCancellable -> do
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
return jCancellable'
maybeCallback <- case callback of
Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
forall a. FunPtr a
FP.nullFunPtr
Just AsyncReadyCallback
jCallback -> do
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
jCallback' <- Gio.Callbacks.mk_AsyncReadyCallback (Gio.Callbacks.wrap_AsyncReadyCallback (Just ptrcallback) (Gio.Callbacks.drop_closures_AsyncReadyCallback jCallback))
poke ptrcallback jCallback'
return jCallback'
let userData = Ptr a
forall a. Ptr a
nullPtr
secret_retrievable_retrieve_secret self' maybeCancellable maybeCallback userData
touchManagedPtr self
whenJust cancellable touchManagedPtr
return ()
#if defined(ENABLE_OVERLOADING)
data RetrievableRetrieveSecretMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsRetrievable a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod RetrievableRetrieveSecretMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRetrievable a, IsCancellable b) =>
a -> Maybe b -> Maybe AsyncReadyCallback -> m ()
retrievableRetrieveSecret
instance O.OverloadedMethodInfo RetrievableRetrieveSecretMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.retrievableRetrieveSecret",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableRetrieveSecret"
})
#endif
foreign import ccall "secret_retrievable_retrieve_secret_finish" secret_retrievable_retrieve_secret_finish ::
Ptr Retrievable ->
Ptr Gio.AsyncResult.AsyncResult ->
Ptr (Ptr GError) ->
IO (Ptr Secret.Value.Value)
retrievableRetrieveSecretFinish ::
(B.CallStack.HasCallStack, MonadIO m, IsRetrievable a, Gio.AsyncResult.IsAsyncResult b) =>
a
-> b
-> m (Maybe Secret.Value.Value)
retrievableRetrieveSecretFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRetrievable a, IsAsyncResult b) =>
a -> b -> m (Maybe Value)
retrievableRetrieveSecretFinish a
self b
result_ = IO (Maybe Value) -> m (Maybe Value)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Value) -> m (Maybe Value))
-> IO (Maybe Value) -> m (Maybe Value)
forall a b. (a -> b) -> a -> b
$ do
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
result_' <- unsafeManagedPtrCastPtr result_
onException (do
result <- propagateGError $ secret_retrievable_retrieve_secret_finish self' result_'
maybeResult <- convertIfNonNull result $ \Ptr Value
result' -> do
result'' <- ((ManagedPtr Value -> Value) -> Ptr Value -> IO Value
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Value -> Value
Secret.Value.Value) Ptr Value
result'
return result''
touchManagedPtr self
touchManagedPtr result_
return maybeResult
) (do
return ()
)
#if defined(ENABLE_OVERLOADING)
data RetrievableRetrieveSecretFinishMethodInfo
instance (signature ~ (b -> m (Maybe Secret.Value.Value)), MonadIO m, IsRetrievable a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod RetrievableRetrieveSecretFinishMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> b -> m (Maybe Value)
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRetrievable a, IsAsyncResult b) =>
a -> b -> m (Maybe Value)
retrievableRetrieveSecretFinish
instance O.OverloadedMethodInfo RetrievableRetrieveSecretFinishMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.retrievableRetrieveSecretFinish",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableRetrieveSecretFinish"
})
#endif
foreign import ccall "secret_retrievable_retrieve_secret_sync" secret_retrievable_retrieve_secret_sync ::
Ptr Retrievable ->
Ptr Gio.Cancellable.Cancellable ->
Ptr (Ptr GError) ->
IO (Ptr Secret.Value.Value)
retrievableRetrieveSecretSync ::
(B.CallStack.HasCallStack, MonadIO m, IsRetrievable a, Gio.Cancellable.IsCancellable b) =>
a
-> Maybe (b)
-> m (Maybe Secret.Value.Value)
retrievableRetrieveSecretSync :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRetrievable a, IsCancellable b) =>
a -> Maybe b -> m (Maybe Value)
retrievableRetrieveSecretSync a
self Maybe b
cancellable = IO (Maybe Value) -> m (Maybe Value)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Value) -> m (Maybe Value))
-> IO (Maybe Value) -> m (Maybe Value)
forall a b. (a -> b) -> a -> b
$ do
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
maybeCancellable <- case cancellable of
Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
FP.nullPtr
Just b
jCancellable -> do
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
return jCancellable'
onException (do
result <- propagateGError $ secret_retrievable_retrieve_secret_sync self' maybeCancellable
maybeResult <- convertIfNonNull result $ \Ptr Value
result' -> do
result'' <- ((ManagedPtr Value -> Value) -> Ptr Value -> IO Value
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Value -> Value
Secret.Value.Value) Ptr Value
result'
return result''
touchManagedPtr self
whenJust cancellable touchManagedPtr
return maybeResult
) (do
return ()
)
#if defined(ENABLE_OVERLOADING)
data RetrievableRetrieveSecretSyncMethodInfo
instance (signature ~ (Maybe (b) -> m (Maybe Secret.Value.Value)), MonadIO m, IsRetrievable a, Gio.Cancellable.IsCancellable b) => O.OverloadedMethod RetrievableRetrieveSecretSyncMethodInfo a signature where
overloadedMethod :: a -> signature
overloadedMethod = a -> signature
a -> Maybe b -> m (Maybe Value)
forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRetrievable a, IsCancellable b) =>
a -> Maybe b -> m (Maybe Value)
retrievableRetrieveSecretSync
instance O.OverloadedMethodInfo RetrievableRetrieveSecretSyncMethodInfo a where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Secret.Interfaces.Retrievable.retrievableRetrieveSecretSync",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-secret-0.0.20/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableRetrieveSecretSync"
})
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Retrievable = RetrievableSignalList
type RetrievableSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif