{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- An object representing a read-only view of a secret item in the
-- Secret Service.
-- 
-- /Since: 0.19.0/

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Secret.Interfaces.Retrievable
    ( 

-- * Exported types
    Retrievable(..)                         ,
    IsRetrievable                           ,
    toRetrievable                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [retrieveSecret]("GI.Secret.Interfaces.Retrievable#g:method:retrieveSecret"), [retrieveSecretFinish]("GI.Secret.Interfaces.Retrievable#g:method:retrieveSecretFinish"), [retrieveSecretSync]("GI.Secret.Interfaces.Retrievable#g:method:retrieveSecretSync"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAttributes]("GI.Secret.Interfaces.Retrievable#g:method:getAttributes"), [getCreated]("GI.Secret.Interfaces.Retrievable#g:method:getCreated"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getLabel]("GI.Secret.Interfaces.Retrievable#g:method:getLabel"), [getModified]("GI.Secret.Interfaces.Retrievable#g:method:getModified"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveRetrievableMethod                ,
#endif

-- ** getAttributes #method:getAttributes#

#if defined(ENABLE_OVERLOADING)
    RetrievableGetAttributesMethodInfo      ,
#endif
    retrievableGetAttributes                ,


-- ** getCreated #method:getCreated#

#if defined(ENABLE_OVERLOADING)
    RetrievableGetCreatedMethodInfo         ,
#endif
    retrievableGetCreated                   ,


-- ** getLabel #method:getLabel#

#if defined(ENABLE_OVERLOADING)
    RetrievableGetLabelMethodInfo           ,
#endif
    retrievableGetLabel                     ,


-- ** getModified #method:getModified#

#if defined(ENABLE_OVERLOADING)
    RetrievableGetModifiedMethodInfo        ,
#endif
    retrievableGetModified                  ,


-- ** retrieveSecret #method:retrieveSecret#

#if defined(ENABLE_OVERLOADING)
    RetrievableRetrieveSecretMethodInfo     ,
#endif
    retrievableRetrieveSecret               ,


-- ** retrieveSecretFinish #method:retrieveSecretFinish#

#if defined(ENABLE_OVERLOADING)
    RetrievableRetrieveSecretFinishMethodInfo,
#endif
    retrievableRetrieveSecretFinish         ,


-- ** retrieveSecretSync #method:retrieveSecretSync#

#if defined(ENABLE_OVERLOADING)
    RetrievableRetrieveSecretSyncMethodInfo ,
#endif
    retrievableRetrieveSecretSync           ,




 -- * Properties


-- ** attributes #attr:attributes#

#if defined(ENABLE_OVERLOADING)
    RetrievableAttributesPropertyInfo       ,
#endif
#if defined(ENABLE_OVERLOADING)
    retrievableAttributes                   ,
#endif


-- ** created #attr:created#
-- | The date and time (in seconds since the UNIX epoch) that this
-- item was created.
-- 
-- /Since: 0.19.0/

#if defined(ENABLE_OVERLOADING)
    RetrievableCreatedPropertyInfo          ,
#endif
    constructRetrievableCreated             ,
    getRetrievableCreated                   ,
#if defined(ENABLE_OVERLOADING)
    retrievableCreated                      ,
#endif
    setRetrievableCreated                   ,


-- ** label #attr:label#
-- | The human readable label for the item.
-- 
-- /Since: 0.19.0/

#if defined(ENABLE_OVERLOADING)
    RetrievableLabelPropertyInfo            ,
#endif
    clearRetrievableLabel                   ,
    constructRetrievableLabel               ,
    getRetrievableLabel                     ,
#if defined(ENABLE_OVERLOADING)
    retrievableLabel                        ,
#endif
    setRetrievableLabel                     ,


-- ** modified #attr:modified#
-- | The date and time (in seconds since the UNIX epoch) that this
-- item was last modified.
-- 
-- /Since: 0.19.0/

#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.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.Text as T
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 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

-- interface Retrievable 
-- | Memory-managed wrapper type.
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
/= :: Retrievable -> Retrievable -> Bool
$c/= :: Retrievable -> Retrievable -> Bool
== :: Retrievable -> Retrievable -> Bool
$c== :: 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

-- | Type class for types which can be safely cast to `Retrievable`, for instance with `toRetrievable`.
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]

-- | Cast to `Retrievable`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
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 (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

-- | Convert 'Retrievable' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
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 Retrievable
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 Retrievable
ptr Ptr Retrievable -> Ptr Retrievable -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Retrievable
forall a. Ptr a
FP.nullPtr
        then Retrievable -> Maybe Retrievable
forall a. a -> Maybe a
P.Just (Retrievable -> Maybe Retrievable)
-> IO Retrievable -> IO (Maybe Retrievable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Retrievable -> Retrievable)
-> Ptr Retrievable -> IO Retrievable
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Retrievable -> Retrievable
Retrievable Ptr Retrievable
ptr
        else Maybe Retrievable -> IO (Maybe Retrievable)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Retrievable
forall a. Maybe a
P.Nothing
        
    

-- XXX Generation of property "attributes" of object "Retrievable" failed.
-- Not implemented: Property RetrievableAttributes has unsupported transfer type TransferEverything
#if defined(ENABLE_OVERLOADING)
-- XXX Placeholder
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 = undefined
    attrSet = undefined
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer = undefined
#endif

-- VVV Prop "created"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@created@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' retrievable #created
-- @
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 (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"

-- | Set the value of the “@created@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' retrievable [ #created 'Data.GI.Base.Attributes.:=' value ]
-- @
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 (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

-- | Construct a `GValueConstruct` with valid value for the “@created@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
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 (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 (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 = getRetrievableCreated
    attrSet = setRetrievableCreated
    attrTransfer _ v = do
        return v
    attrConstruct = constructRetrievableCreated
    attrClear = undefined
#endif

-- VVV Prop "label"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' retrievable #label
-- @
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 (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"

-- | Set the value of the “@label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' retrievable [ #label 'Data.GI.Base.Attributes.:=' value ]
-- @
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 (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)

-- | Construct a `GValueConstruct` with valid value for the “@label@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
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 (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 (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)

-- | Set the value of the “@label@” property to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #label
-- @
clearRetrievableLabel :: (MonadIO m, IsRetrievable o) => o -> m ()
clearRetrievableLabel :: forall (m :: * -> *) o. (MonadIO m, IsRetrievable o) => o -> m ()
clearRetrievableLabel o
obj = IO () -> m ()
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 = getRetrievableLabel
    attrSet = setRetrievableLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructRetrievableLabel
    attrClear = clearRetrievableLabel
#endif

-- VVV Prop "modified"
   -- Type: TBasicType TUInt64
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@modified@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' retrievable #modified
-- @
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 (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"

-- | Set the value of the “@modified@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' retrievable [ #modified 'Data.GI.Base.Attributes.:=' value ]
-- @
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 (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

-- | Construct a `GValueConstruct` with valid value for the “@modified@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
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 (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 (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 = getRetrievableModified
    attrSet = setRetrievableModified
    attrTransfer _ v = do
        return v
    attrConstruct = constructRetrievableModified
    attrClear = undefined
#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, *)])
#endif

#if defined(ENABLE_OVERLOADING)
retrievableAttributes :: AttrLabelProxy "attributes"
retrievableAttributes = AttrLabelProxy

retrievableCreated :: AttrLabelProxy "created"
retrievableCreated = AttrLabelProxy

retrievableLabel :: AttrLabelProxy "label"
retrievableLabel = AttrLabelProxy

retrievableModified :: AttrLabelProxy "modified"
retrievableModified = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveRetrievableMethod (t :: Symbol) (o :: *) :: * 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 = 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 = 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 = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- method Retrievable::get_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Secret" , name = "Retrievable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a retrievable object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TGHash (TBasicType TUTF8) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "secret_retrievable_get_attributes" secret_retrievable_get_attributes :: 
    Ptr Retrievable ->                      -- self : TInterface (Name {namespace = "Secret", name = "Retrievable"})
    IO (Ptr (GHashTable CString CString))

-- | Get the attributes of this object.
-- 
-- The attributes are a mapping of string keys to string values.
-- Attributes are used to search for items. Attributes are not stored
-- or transferred securely by the secret service.
-- 
-- Do not modify the attribute returned by this method.
-- 
-- /Since: 0.19.0/
retrievableGetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsRetrievable a) =>
    a
    -- ^ /@self@/: a retrievable object
    -> m (Map.Map T.Text T.Text)
    -- ^ __Returns:__ a new reference
    --          to the attributes, which should not be modified, and
    --          released with 'GI.GLib.Functions.hashTableUnref'
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 (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
    Ptr Retrievable
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr (GHashTable CString CString)
result <- Ptr Retrievable -> IO (Ptr (GHashTable CString CString))
secret_retrievable_get_attributes Ptr Retrievable
self'
    Text -> Ptr (GHashTable CString CString) -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"retrievableGetAttributes" Ptr (GHashTable CString CString)
result
    [(PtrWrapped CString, PtrWrapped CString)]
result' <- Ptr (GHashTable CString CString)
-> IO [(PtrWrapped CString, PtrWrapped CString)]
forall a b.
Ptr (GHashTable a b) -> IO [(PtrWrapped a, PtrWrapped b)]
unpackGHashTable Ptr (GHashTable CString CString)
result
    let result'' :: [(CString, PtrWrapped CString)]
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
cstringUnpackPtr [(PtrWrapped CString, PtrWrapped CString)]
result'
    [(Text, PtrWrapped CString)]
result''' <- (CString -> IO Text)
-> [(CString, PtrWrapped CString)]
-> IO [(Text, PtrWrapped CString)]
forall (f :: * -> *) a c b.
Applicative f =>
(a -> f c) -> [(a, b)] -> f [(c, b)]
mapFirstA HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [(CString, PtrWrapped CString)]
result''
    let result'''' :: [(Text, CString)]
result'''' = (PtrWrapped CString -> CString)
-> [(Text, PtrWrapped CString)] -> [(Text, CString)]
forall b c a. (b -> c) -> [(a, b)] -> [(a, c)]
mapSecond PtrWrapped CString -> CString
cstringUnpackPtr [(Text, PtrWrapped CString)]
result'''
    [(Text, Text)]
result''''' <- (CString -> IO Text) -> [(Text, CString)] -> IO [(Text, Text)]
forall (f :: * -> *) b c a.
Applicative f =>
(b -> f c) -> [(a, b)] -> f [(a, c)]
mapSecondA HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText [(Text, CString)]
result''''
    let result'''''' :: Map Text Text
result'''''' = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [(Text, Text)]
result'''''
    Ptr (GHashTable CString CString) -> IO ()
forall a b. Ptr (GHashTable a b) -> IO ()
unrefGHashTable Ptr (GHashTable CString CString)
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Map Text Text -> IO (Map Text Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Map Text Text
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 = retrievableGetAttributes

instance O.OverloadedMethodInfo RetrievableGetAttributesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Secret.Interfaces.Retrievable.retrievableGetAttributes",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-secret-0.0.13/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableGetAttributes"
        }


#endif

-- method Retrievable::get_created
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Secret" , name = "Retrievable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a retrievable object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "secret_retrievable_get_created" secret_retrievable_get_created :: 
    Ptr Retrievable ->                      -- self : TInterface (Name {namespace = "Secret", name = "Retrievable"})
    IO Word64

-- | Get the created date and time of the object. The return value is
-- the number of seconds since the unix epoch, January 1st 1970.
-- 
-- /Since: 0.19.0/
retrievableGetCreated ::
    (B.CallStack.HasCallStack, MonadIO m, IsRetrievable a) =>
    a
    -- ^ /@self@/: a retrievable object
    -> m Word64
    -- ^ __Returns:__ the created date and time
retrievableGetCreated :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m Word64
retrievableGetCreated a
self = IO Word64 -> m Word64
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
    Ptr Retrievable
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word64
result <- Ptr Retrievable -> IO Word64
secret_retrievable_get_created Ptr Retrievable
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data RetrievableGetCreatedMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsRetrievable a) => O.OverloadedMethod RetrievableGetCreatedMethodInfo a signature where
    overloadedMethod = retrievableGetCreated

instance O.OverloadedMethodInfo RetrievableGetCreatedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Secret.Interfaces.Retrievable.retrievableGetCreated",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-secret-0.0.13/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableGetCreated"
        }


#endif

-- method Retrievable::get_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Secret" , name = "Retrievable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a retrievable object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "secret_retrievable_get_label" secret_retrievable_get_label :: 
    Ptr Retrievable ->                      -- self : TInterface (Name {namespace = "Secret", name = "Retrievable"})
    IO CString

-- | Get the label of this item.
-- 
-- /Since: 0.19.0/
retrievableGetLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsRetrievable a) =>
    a
    -- ^ /@self@/: a retrievable object
    -> m T.Text
    -- ^ __Returns:__ the label, which should be freed with 'GI.GLib.Functions.free'
retrievableGetLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m Text
retrievableGetLabel a
self = IO Text -> m Text
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
    Ptr Retrievable
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr Retrievable -> IO CString
secret_retrievable_get_label Ptr Retrievable
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"retrievableGetLabel" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data RetrievableGetLabelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsRetrievable a) => O.OverloadedMethod RetrievableGetLabelMethodInfo a signature where
    overloadedMethod = retrievableGetLabel

instance O.OverloadedMethodInfo RetrievableGetLabelMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Secret.Interfaces.Retrievable.retrievableGetLabel",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-secret-0.0.13/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableGetLabel"
        }


#endif

-- method Retrievable::get_modified
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Secret" , name = "Retrievable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a retrievable object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : False
-- Skip return : False

foreign import ccall "secret_retrievable_get_modified" secret_retrievable_get_modified :: 
    Ptr Retrievable ->                      -- self : TInterface (Name {namespace = "Secret", name = "Retrievable"})
    IO Word64

-- | Get the modified date and time of the object. The return value is
-- the number of seconds since the unix epoch, January 1st 1970.
-- 
-- /Since: 0.19.0/
retrievableGetModified ::
    (B.CallStack.HasCallStack, MonadIO m, IsRetrievable a) =>
    a
    -- ^ /@self@/: a retrievable object
    -> m Word64
    -- ^ __Returns:__ the modified date and time
retrievableGetModified :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRetrievable a) =>
a -> m Word64
retrievableGetModified a
self = IO Word64 -> m Word64
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
    Ptr Retrievable
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Word64
result <- Ptr Retrievable -> IO Word64
secret_retrievable_get_modified Ptr Retrievable
self'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Word64 -> IO Word64
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result

#if defined(ENABLE_OVERLOADING)
data RetrievableGetModifiedMethodInfo
instance (signature ~ (m Word64), MonadIO m, IsRetrievable a) => O.OverloadedMethod RetrievableGetModifiedMethodInfo a signature where
    overloadedMethod = retrievableGetModified

instance O.OverloadedMethodInfo RetrievableGetModifiedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Secret.Interfaces.Retrievable.retrievableGetModified",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-secret-0.0.13/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableGetModified"
        }


#endif

-- method Retrievable::retrieve_secret
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Secret" , name = "Retrievable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a retrievable object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "optional cancellation object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "called when the operation completes"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 3
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to the callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "secret_retrievable_retrieve_secret" secret_retrievable_retrieve_secret :: 
    Ptr Retrievable ->                      -- self : TInterface (Name {namespace = "Secret", name = "Retrievable"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Retrieve the secret value of this object.
-- 
-- Each retrievable object has a single secret which might be a
-- password or some other secret binary value.
-- 
-- This function returns immediately and completes asynchronously.
-- 
-- /Since: 0.19.0/
retrievableRetrieveSecret ::
    (B.CallStack.HasCallStack, MonadIO m, IsRetrievable a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@self@/: a retrievable object
    -> Maybe (b)
    -- ^ /@cancellable@/: optional cancellation object
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: called when the operation completes
    -> 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 (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr Retrievable
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr Retrievable
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
secret_retrievable_retrieve_secret Ptr Retrievable
self' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
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 = retrievableRetrieveSecret

instance O.OverloadedMethodInfo RetrievableRetrieveSecretMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Secret.Interfaces.Retrievable.retrievableRetrieveSecret",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-secret-0.0.13/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableRetrieveSecret"
        }


#endif

-- method Retrievable::retrieve_secret_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Secret" , name = "Retrievable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a retrievable object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "asynchronous result passed to callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Secret" , name = "Value" })
-- throws : True
-- Skip return : False

foreign import ccall "secret_retrievable_retrieve_secret_finish" secret_retrievable_retrieve_secret_finish :: 
    Ptr Retrievable ->                      -- self : TInterface (Name {namespace = "Secret", name = "Retrievable"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Secret.Value.Value)

-- | Complete asynchronous operation to retrieve the secret value of this object.
-- 
-- /Since: 0.19.0/
retrievableRetrieveSecretFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsRetrievable a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@self@/: a retrievable object
    -> b
    -- ^ /@result@/: asynchronous result passed to callback
    -> m (Maybe Secret.Value.Value)
    -- ^ __Returns:__ the secret value which should be
    --          released with 'GI.Secret.Structs.Value.valueUnref', or 'P.Nothing' /(Can throw 'Data.GI.Base.GError.GError')/
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 (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
    Ptr Retrievable
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO (Maybe Value) -> IO () -> IO (Maybe Value)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Value
result <- (Ptr (Ptr GError) -> IO (Ptr Value)) -> IO (Ptr Value)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Value)) -> IO (Ptr Value))
-> (Ptr (Ptr GError) -> IO (Ptr Value)) -> IO (Ptr Value)
forall a b. (a -> b) -> a -> b
$ Ptr Retrievable
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr Value)
secret_retrievable_retrieve_secret_finish Ptr Retrievable
self' Ptr AsyncResult
result_'
        Maybe Value
maybeResult <- Ptr Value -> (Ptr Value -> IO Value) -> IO (Maybe Value)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Value
result ((Ptr Value -> IO Value) -> IO (Maybe Value))
-> (Ptr Value -> IO Value) -> IO (Maybe Value)
forall a b. (a -> b) -> a -> b
$ \Ptr Value
result' -> do
            Value
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'
            Value -> IO Value
forall (m :: * -> *) a. Monad m => a -> m a
return Value
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        Maybe Value -> IO (Maybe Value)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Value
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
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 = retrievableRetrieveSecretFinish

instance O.OverloadedMethodInfo RetrievableRetrieveSecretFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Secret.Interfaces.Retrievable.retrievableRetrieveSecretFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-secret-0.0.13/docs/GI-Secret-Interfaces-Retrievable.html#v:retrievableRetrieveSecretFinish"
        }


#endif

-- method Retrievable::retrieve_secret_sync
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Secret" , name = "Retrievable" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a retrievable object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "optional cancellation object"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Secret" , name = "Value" })
-- throws : True
-- Skip return : False

foreign import ccall "secret_retrievable_retrieve_secret_sync" secret_retrievable_retrieve_secret_sync :: 
    Ptr Retrievable ->                      -- self : TInterface (Name {namespace = "Secret", name = "Retrievable"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Secret.Value.Value)

-- | Retrieve the secret value of this object synchronously.
-- 
-- Each retrievable object has a single secret which might be a
-- password or some other secret binary value.
-- 
-- This method may block indefinitely and should not be used in user interface
-- threads.
-- 
-- /Since: 0.19.0/
retrievableRetrieveSecretSync ::
    (B.CallStack.HasCallStack, MonadIO m, IsRetrievable a, Gio.Cancellable.IsCancellable b) =>
    a
    -- ^ /@self@/: a retrievable object
    -> Maybe (b)
    -- ^ /@cancellable@/: optional cancellation object
    -> m (Maybe Secret.Value.Value)
    -- ^ __Returns:__ the secret value which should be
    --          released with 'GI.Secret.Structs.Value.valueUnref', or 'P.Nothing' /(Can throw 'Data.GI.Base.GError.GError')/
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 (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
    Ptr Retrievable
self' <- a -> IO (Ptr Retrievable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Cancellable
maybeCancellable <- case Maybe b
cancellable of
        Maybe b
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just b
jCancellable -> do
            Ptr Cancellable
jCancellable' <- b -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    IO (Maybe Value) -> IO () -> IO (Maybe Value)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Value
result <- (Ptr (Ptr GError) -> IO (Ptr Value)) -> IO (Ptr Value)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Value)) -> IO (Ptr Value))
-> (Ptr (Ptr GError) -> IO (Ptr Value)) -> IO (Ptr Value)
forall a b. (a -> b) -> a -> b
$ Ptr Retrievable
-> Ptr Cancellable -> Ptr (Ptr GError) -> IO (Ptr Value)
secret_retrievable_retrieve_secret_sync Ptr Retrievable
self' Ptr Cancellable
maybeCancellable
        Maybe Value
maybeResult <- Ptr Value -> (Ptr Value -> IO Value) -> IO (Maybe Value)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Value
result ((Ptr Value -> IO Value) -> IO (Maybe Value))
-> (Ptr Value -> IO Value) -> IO (Maybe Value)
forall a b. (a -> b) -> a -> b
$ \Ptr Value
result' -> do
            Value
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'
            Value -> IO Value
forall (m :: * -> *) a. Monad m => a -> m a
return Value
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
cancellable b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        Maybe Value -> IO (Maybe Value)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Value
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
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 = retrievableRetrieveSecretSync

instance O.OverloadedMethodInfo RetrievableRetrieveSecretSyncMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Secret.Interfaces.Retrievable.retrievableRetrieveSecretSync",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-secret-0.0.13/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, *)])

#endif