{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Dazzle.Objects.SettingsSandwich
(
#if defined(ENABLE_OVERLOADING)
SettingsSandwichBindWithMappingMethodInfo,
#endif
SettingsSandwich(..) ,
IsSettingsSandwich ,
toSettingsSandwich ,
#if defined(ENABLE_OVERLOADING)
ResolveSettingsSandwichMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SettingsSandwichAppendMethodInfo ,
#endif
settingsSandwichAppend ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichBindMethodInfo ,
#endif
settingsSandwichBind ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichGetBooleanMethodInfo ,
#endif
settingsSandwichGetBoolean ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichGetDefaultValueMethodInfo,
#endif
settingsSandwichGetDefaultValue ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichGetDoubleMethodInfo ,
#endif
settingsSandwichGetDouble ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichGetIntMethodInfo ,
#endif
settingsSandwichGetInt ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichGetStringMethodInfo ,
#endif
settingsSandwichGetString ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichGetUintMethodInfo ,
#endif
settingsSandwichGetUint ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichGetUserValueMethodInfo ,
#endif
settingsSandwichGetUserValue ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichGetValueMethodInfo ,
#endif
settingsSandwichGetValue ,
settingsSandwichNew ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichSetBooleanMethodInfo ,
#endif
settingsSandwichSetBoolean ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichSetDoubleMethodInfo ,
#endif
settingsSandwichSetDouble ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichSetIntMethodInfo ,
#endif
settingsSandwichSetInt ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichSetStringMethodInfo ,
#endif
settingsSandwichSetString ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichSetUintMethodInfo ,
#endif
settingsSandwichSetUint ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichSetValueMethodInfo ,
#endif
settingsSandwichSetValue ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichUnbindMethodInfo ,
#endif
settingsSandwichUnbind ,
#if defined(ENABLE_OVERLOADING)
SettingsSandwichPathPropertyInfo ,
#endif
constructSettingsSandwichPath ,
getSettingsSandwichPath ,
#if defined(ENABLE_OVERLOADING)
settingsSandwichPath ,
#endif
#if defined(ENABLE_OVERLOADING)
SettingsSandwichSchemaIdPropertyInfo ,
#endif
constructSettingsSandwichSchemaId ,
getSettingsSandwichSchemaId ,
#if defined(ENABLE_OVERLOADING)
settingsSandwichSchemaId ,
#endif
) 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.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Objects.Settings as Gio.Settings
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Objects.Settings as Gio.Settings
#endif
newtype SettingsSandwich = SettingsSandwich (SP.ManagedPtr SettingsSandwich)
deriving (SettingsSandwich -> SettingsSandwich -> Bool
(SettingsSandwich -> SettingsSandwich -> Bool)
-> (SettingsSandwich -> SettingsSandwich -> Bool)
-> Eq SettingsSandwich
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SettingsSandwich -> SettingsSandwich -> Bool
== :: SettingsSandwich -> SettingsSandwich -> Bool
$c/= :: SettingsSandwich -> SettingsSandwich -> Bool
/= :: SettingsSandwich -> SettingsSandwich -> Bool
Eq)
instance SP.ManagedPtrNewtype SettingsSandwich where
toManagedPtr :: SettingsSandwich -> ManagedPtr SettingsSandwich
toManagedPtr (SettingsSandwich ManagedPtr SettingsSandwich
p) = ManagedPtr SettingsSandwich
p
foreign import ccall "dzl_settings_sandwich_get_type"
c_dzl_settings_sandwich_get_type :: IO B.Types.GType
instance B.Types.TypedObject SettingsSandwich where
glibType :: IO GType
glibType = IO GType
c_dzl_settings_sandwich_get_type
instance B.Types.GObject SettingsSandwich
class (SP.GObject o, O.IsDescendantOf SettingsSandwich o) => IsSettingsSandwich o
instance (SP.GObject o, O.IsDescendantOf SettingsSandwich o) => IsSettingsSandwich o
instance O.HasParentTypes SettingsSandwich
type instance O.ParentTypes SettingsSandwich = '[GObject.Object.Object]
toSettingsSandwich :: (MIO.MonadIO m, IsSettingsSandwich o) => o -> m SettingsSandwich
toSettingsSandwich :: forall (m :: * -> *) o.
(MonadIO m, IsSettingsSandwich o) =>
o -> m SettingsSandwich
toSettingsSandwich = IO SettingsSandwich -> m SettingsSandwich
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO SettingsSandwich -> m SettingsSandwich)
-> (o -> IO SettingsSandwich) -> o -> m SettingsSandwich
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr SettingsSandwich -> SettingsSandwich)
-> o -> IO SettingsSandwich
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr SettingsSandwich -> SettingsSandwich
SettingsSandwich
instance B.GValue.IsGValue (Maybe SettingsSandwich) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_dzl_settings_sandwich_get_type
gvalueSet_ :: Ptr GValue -> Maybe SettingsSandwich -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SettingsSandwich
P.Nothing = Ptr GValue -> Ptr SettingsSandwich -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr SettingsSandwich
forall a. Ptr a
FP.nullPtr :: FP.Ptr SettingsSandwich)
gvalueSet_ Ptr GValue
gv (P.Just SettingsSandwich
obj) = SettingsSandwich -> (Ptr SettingsSandwich -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SettingsSandwich
obj (Ptr GValue -> Ptr SettingsSandwich -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe SettingsSandwich)
gvalueGet_ Ptr GValue
gv = do
Ptr SettingsSandwich
ptr <- Ptr GValue -> IO (Ptr SettingsSandwich)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr SettingsSandwich)
if Ptr SettingsSandwich
ptr Ptr SettingsSandwich -> Ptr SettingsSandwich -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr SettingsSandwich
forall a. Ptr a
FP.nullPtr
then SettingsSandwich -> Maybe SettingsSandwich
forall a. a -> Maybe a
P.Just (SettingsSandwich -> Maybe SettingsSandwich)
-> IO SettingsSandwich -> IO (Maybe SettingsSandwich)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr SettingsSandwich -> SettingsSandwich)
-> Ptr SettingsSandwich -> IO SettingsSandwich
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr SettingsSandwich -> SettingsSandwich
SettingsSandwich Ptr SettingsSandwich
ptr
else Maybe SettingsSandwich -> IO (Maybe SettingsSandwich)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SettingsSandwich
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveSettingsSandwichMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveSettingsSandwichMethod "append" o = SettingsSandwichAppendMethodInfo
ResolveSettingsSandwichMethod "bind" o = SettingsSandwichBindMethodInfo
ResolveSettingsSandwichMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveSettingsSandwichMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveSettingsSandwichMethod "bindWithMapping" o = SettingsSandwichBindWithMappingMethodInfo
ResolveSettingsSandwichMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveSettingsSandwichMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveSettingsSandwichMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveSettingsSandwichMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveSettingsSandwichMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveSettingsSandwichMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveSettingsSandwichMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveSettingsSandwichMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveSettingsSandwichMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveSettingsSandwichMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveSettingsSandwichMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveSettingsSandwichMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveSettingsSandwichMethod "unbind" o = SettingsSandwichUnbindMethodInfo
ResolveSettingsSandwichMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveSettingsSandwichMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveSettingsSandwichMethod "getBoolean" o = SettingsSandwichGetBooleanMethodInfo
ResolveSettingsSandwichMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveSettingsSandwichMethod "getDefaultValue" o = SettingsSandwichGetDefaultValueMethodInfo
ResolveSettingsSandwichMethod "getDouble" o = SettingsSandwichGetDoubleMethodInfo
ResolveSettingsSandwichMethod "getInt" o = SettingsSandwichGetIntMethodInfo
ResolveSettingsSandwichMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveSettingsSandwichMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveSettingsSandwichMethod "getString" o = SettingsSandwichGetStringMethodInfo
ResolveSettingsSandwichMethod "getUint" o = SettingsSandwichGetUintMethodInfo
ResolveSettingsSandwichMethod "getUserValue" o = SettingsSandwichGetUserValueMethodInfo
ResolveSettingsSandwichMethod "getValue" o = SettingsSandwichGetValueMethodInfo
ResolveSettingsSandwichMethod "setBoolean" o = SettingsSandwichSetBooleanMethodInfo
ResolveSettingsSandwichMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveSettingsSandwichMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveSettingsSandwichMethod "setDouble" o = SettingsSandwichSetDoubleMethodInfo
ResolveSettingsSandwichMethod "setInt" o = SettingsSandwichSetIntMethodInfo
ResolveSettingsSandwichMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveSettingsSandwichMethod "setString" o = SettingsSandwichSetStringMethodInfo
ResolveSettingsSandwichMethod "setUint" o = SettingsSandwichSetUintMethodInfo
ResolveSettingsSandwichMethod "setValue" o = SettingsSandwichSetValueMethodInfo
ResolveSettingsSandwichMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSettingsSandwichMethod t SettingsSandwich, O.OverloadedMethod info SettingsSandwich p) => OL.IsLabel t (SettingsSandwich -> 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 ~ ResolveSettingsSandwichMethod t SettingsSandwich, O.OverloadedMethod info SettingsSandwich p, R.HasField t SettingsSandwich p) => R.HasField t SettingsSandwich p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveSettingsSandwichMethod t SettingsSandwich, O.OverloadedMethodInfo info SettingsSandwich) => OL.IsLabel t (O.MethodProxy info SettingsSandwich) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getSettingsSandwichPath :: (MonadIO m, IsSettingsSandwich o) => o -> m (Maybe T.Text)
getSettingsSandwichPath :: forall (m :: * -> *) o.
(MonadIO m, IsSettingsSandwich o) =>
o -> m (Maybe Text)
getSettingsSandwichPath 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
"path"
constructSettingsSandwichPath :: (IsSettingsSandwich o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingsSandwichPath :: forall o (m :: * -> *).
(IsSettingsSandwich o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingsSandwichPath 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
"path" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichPathPropertyInfo
instance AttrInfo SettingsSandwichPathPropertyInfo where
type AttrAllowedOps SettingsSandwichPathPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint SettingsSandwichPathPropertyInfo = IsSettingsSandwich
type AttrSetTypeConstraint SettingsSandwichPathPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint SettingsSandwichPathPropertyInfo = (~) T.Text
type AttrTransferType SettingsSandwichPathPropertyInfo = T.Text
type AttrGetType SettingsSandwichPathPropertyInfo = (Maybe T.Text)
type AttrLabel SettingsSandwichPathPropertyInfo = "path"
type AttrOrigin SettingsSandwichPathPropertyInfo = SettingsSandwich
attrGet = getSettingsSandwichPath
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructSettingsSandwichPath
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.path"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#g:attr:path"
})
#endif
getSettingsSandwichSchemaId :: (MonadIO m, IsSettingsSandwich o) => o -> m (Maybe T.Text)
getSettingsSandwichSchemaId :: forall (m :: * -> *) o.
(MonadIO m, IsSettingsSandwich o) =>
o -> m (Maybe Text)
getSettingsSandwichSchemaId 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
"schema-id"
constructSettingsSandwichSchemaId :: (IsSettingsSandwich o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructSettingsSandwichSchemaId :: forall o (m :: * -> *).
(IsSettingsSandwich o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructSettingsSandwichSchemaId 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
"schema-id" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichSchemaIdPropertyInfo
instance AttrInfo SettingsSandwichSchemaIdPropertyInfo where
type AttrAllowedOps SettingsSandwichSchemaIdPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint SettingsSandwichSchemaIdPropertyInfo = IsSettingsSandwich
type AttrSetTypeConstraint SettingsSandwichSchemaIdPropertyInfo = (~) T.Text
type AttrTransferTypeConstraint SettingsSandwichSchemaIdPropertyInfo = (~) T.Text
type AttrTransferType SettingsSandwichSchemaIdPropertyInfo = T.Text
type AttrGetType SettingsSandwichSchemaIdPropertyInfo = (Maybe T.Text)
type AttrLabel SettingsSandwichSchemaIdPropertyInfo = "schema-id"
type AttrOrigin SettingsSandwichSchemaIdPropertyInfo = SettingsSandwich
attrGet = getSettingsSandwichSchemaId
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructSettingsSandwichSchemaId
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.schemaId"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#g:attr:schemaId"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingsSandwich
type instance O.AttributeList SettingsSandwich = SettingsSandwichAttributeList
type SettingsSandwichAttributeList = ('[ '("path", SettingsSandwichPathPropertyInfo), '("schemaId", SettingsSandwichSchemaIdPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
settingsSandwichPath :: AttrLabelProxy "path"
settingsSandwichPath = AttrLabelProxy
settingsSandwichSchemaId :: AttrLabelProxy "schemaId"
settingsSandwichSchemaId = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList SettingsSandwich = SettingsSandwichSignalList
type SettingsSandwichSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "dzl_settings_sandwich_new" dzl_settings_sandwich_new ::
CString ->
CString ->
IO (Ptr SettingsSandwich)
settingsSandwichNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> T.Text
-> m SettingsSandwich
settingsSandwichNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Text -> m SettingsSandwich
settingsSandwichNew Text
schemaId Text
path = IO SettingsSandwich -> m SettingsSandwich
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingsSandwich -> m SettingsSandwich)
-> IO SettingsSandwich -> m SettingsSandwich
forall a b. (a -> b) -> a -> b
$ do
CString
schemaId' <- Text -> IO CString
textToCString Text
schemaId
CString
path' <- Text -> IO CString
textToCString Text
path
Ptr SettingsSandwich
result <- CString -> CString -> IO (Ptr SettingsSandwich)
dzl_settings_sandwich_new CString
schemaId' CString
path'
Text -> Ptr SettingsSandwich -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingsSandwichNew" Ptr SettingsSandwich
result
SettingsSandwich
result' <- ((ManagedPtr SettingsSandwich -> SettingsSandwich)
-> Ptr SettingsSandwich -> IO SettingsSandwich
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr SettingsSandwich -> SettingsSandwich
SettingsSandwich) Ptr SettingsSandwich
result
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
schemaId'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
path'
SettingsSandwich -> IO SettingsSandwich
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return SettingsSandwich
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "dzl_settings_sandwich_append" dzl_settings_sandwich_append ::
Ptr SettingsSandwich ->
Ptr Gio.Settings.Settings ->
IO ()
settingsSandwichAppend ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a, Gio.Settings.IsSettings b) =>
a
-> b
-> m ()
settingsSandwichAppend :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsSettingsSandwich a, IsSettings b) =>
a -> b -> m ()
settingsSandwichAppend a
self b
settings = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
Ptr Settings
settings' <- b -> IO (Ptr Settings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
settings
Ptr SettingsSandwich -> Ptr Settings -> IO ()
dzl_settings_sandwich_append Ptr SettingsSandwich
self' Ptr Settings
settings'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
settings
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichAppendMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsSettingsSandwich a, Gio.Settings.IsSettings b) => O.OverloadedMethod SettingsSandwichAppendMethodInfo a signature where
overloadedMethod = settingsSandwichAppend
instance O.OverloadedMethodInfo SettingsSandwichAppendMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichAppend",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichAppend"
})
#endif
foreign import ccall "dzl_settings_sandwich_bind" dzl_settings_sandwich_bind ::
Ptr SettingsSandwich ->
CString ->
Ptr () ->
CString ->
CUInt ->
IO ()
settingsSandwichBind ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> Ptr ()
-> T.Text
-> [Gio.Flags.SettingsBindFlags]
-> m ()
settingsSandwichBind :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> Ptr () -> Text -> [SettingsBindFlags] -> m ()
settingsSandwichBind a
self Text
key Ptr ()
object Text
property [SettingsBindFlags]
flags = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
CString
property' <- Text -> IO CString
textToCString Text
property
let flags' :: CUInt
flags' = [SettingsBindFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [SettingsBindFlags]
flags
Ptr SettingsSandwich
-> CString -> Ptr () -> CString -> CUInt -> IO ()
dzl_settings_sandwich_bind Ptr SettingsSandwich
self' CString
key' Ptr ()
object CString
property' CUInt
flags'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichBindMethodInfo
instance (signature ~ (T.Text -> Ptr () -> T.Text -> [Gio.Flags.SettingsBindFlags] -> m ()), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichBindMethodInfo a signature where
overloadedMethod = settingsSandwichBind
instance O.OverloadedMethodInfo SettingsSandwichBindMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichBind",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichBind"
})
#endif
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichBindWithMappingMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "bindWithMapping" SettingsSandwich) => O.OverloadedMethod SettingsSandwichBindWithMappingMethodInfo o p where
overloadedMethod = undefined
instance (o ~ O.UnsupportedMethodError "bindWithMapping" SettingsSandwich) => O.OverloadedMethodInfo SettingsSandwichBindWithMappingMethodInfo o where
overloadedMethodInfo = undefined
#endif
foreign import ccall "dzl_settings_sandwich_get_boolean" dzl_settings_sandwich_get_boolean ::
Ptr SettingsSandwich ->
CString ->
IO CInt
settingsSandwichGetBoolean ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> m Bool
settingsSandwichGetBoolean :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> m Bool
settingsSandwichGetBoolean a
self Text
key = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
CInt
result <- Ptr SettingsSandwich -> CString -> IO CInt
dzl_settings_sandwich_get_boolean Ptr SettingsSandwich
self' CString
key'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichGetBooleanMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichGetBooleanMethodInfo a signature where
overloadedMethod = settingsSandwichGetBoolean
instance O.OverloadedMethodInfo SettingsSandwichGetBooleanMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichGetBoolean",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichGetBoolean"
})
#endif
foreign import ccall "dzl_settings_sandwich_get_default_value" dzl_settings_sandwich_get_default_value ::
Ptr SettingsSandwich ->
CString ->
IO (Ptr GVariant)
settingsSandwichGetDefaultValue ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> m GVariant
settingsSandwichGetDefaultValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> m GVariant
settingsSandwichGetDefaultValue a
self Text
key = IO GVariant -> m GVariant
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
Ptr GVariant
result <- Ptr SettingsSandwich -> CString -> IO (Ptr GVariant)
dzl_settings_sandwich_get_default_value Ptr SettingsSandwich
self' CString
key'
Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingsSandwichGetDefaultValue" Ptr GVariant
result
GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
GVariant -> IO GVariant
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichGetDefaultValueMethodInfo
instance (signature ~ (T.Text -> m GVariant), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichGetDefaultValueMethodInfo a signature where
overloadedMethod = settingsSandwichGetDefaultValue
instance O.OverloadedMethodInfo SettingsSandwichGetDefaultValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichGetDefaultValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichGetDefaultValue"
})
#endif
foreign import ccall "dzl_settings_sandwich_get_double" dzl_settings_sandwich_get_double ::
Ptr SettingsSandwich ->
CString ->
IO CDouble
settingsSandwichGetDouble ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> m Double
settingsSandwichGetDouble :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> m Double
settingsSandwichGetDouble a
self Text
key = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
CDouble
result <- Ptr SettingsSandwich -> CString -> IO CDouble
dzl_settings_sandwich_get_double Ptr SettingsSandwich
self' CString
key'
let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichGetDoubleMethodInfo
instance (signature ~ (T.Text -> m Double), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichGetDoubleMethodInfo a signature where
overloadedMethod = settingsSandwichGetDouble
instance O.OverloadedMethodInfo SettingsSandwichGetDoubleMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichGetDouble",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichGetDouble"
})
#endif
foreign import ccall "dzl_settings_sandwich_get_int" dzl_settings_sandwich_get_int ::
Ptr SettingsSandwich ->
CString ->
IO Int32
settingsSandwichGetInt ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> m Int32
settingsSandwichGetInt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> m Int32
settingsSandwichGetInt a
self Text
key = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
Int32
result <- Ptr SettingsSandwich -> CString -> IO Int32
dzl_settings_sandwich_get_int Ptr SettingsSandwich
self' CString
key'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichGetIntMethodInfo
instance (signature ~ (T.Text -> m Int32), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichGetIntMethodInfo a signature where
overloadedMethod = settingsSandwichGetInt
instance O.OverloadedMethodInfo SettingsSandwichGetIntMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichGetInt",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichGetInt"
})
#endif
foreign import ccall "dzl_settings_sandwich_get_string" dzl_settings_sandwich_get_string ::
Ptr SettingsSandwich ->
CString ->
IO CString
settingsSandwichGetString ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> m T.Text
settingsSandwichGetString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> m Text
settingsSandwichGetString a
self Text
key = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
CString
result <- Ptr SettingsSandwich -> CString -> IO CString
dzl_settings_sandwich_get_string Ptr SettingsSandwich
self' CString
key'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingsSandwichGetString" 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
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichGetStringMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichGetStringMethodInfo a signature where
overloadedMethod = settingsSandwichGetString
instance O.OverloadedMethodInfo SettingsSandwichGetStringMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichGetString",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichGetString"
})
#endif
foreign import ccall "dzl_settings_sandwich_get_uint" dzl_settings_sandwich_get_uint ::
Ptr SettingsSandwich ->
CString ->
IO Word32
settingsSandwichGetUint ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> m Word32
settingsSandwichGetUint :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> m Word32
settingsSandwichGetUint a
self Text
key = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
Word32
result <- Ptr SettingsSandwich -> CString -> IO Word32
dzl_settings_sandwich_get_uint Ptr SettingsSandwich
self' CString
key'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichGetUintMethodInfo
instance (signature ~ (T.Text -> m Word32), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichGetUintMethodInfo a signature where
overloadedMethod = settingsSandwichGetUint
instance O.OverloadedMethodInfo SettingsSandwichGetUintMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichGetUint",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichGetUint"
})
#endif
foreign import ccall "dzl_settings_sandwich_get_user_value" dzl_settings_sandwich_get_user_value ::
Ptr SettingsSandwich ->
CString ->
IO (Ptr GVariant)
settingsSandwichGetUserValue ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> m GVariant
settingsSandwichGetUserValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> m GVariant
settingsSandwichGetUserValue a
self Text
key = IO GVariant -> m GVariant
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
Ptr GVariant
result <- Ptr SettingsSandwich -> CString -> IO (Ptr GVariant)
dzl_settings_sandwich_get_user_value Ptr SettingsSandwich
self' CString
key'
Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingsSandwichGetUserValue" Ptr GVariant
result
GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
GVariant -> IO GVariant
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichGetUserValueMethodInfo
instance (signature ~ (T.Text -> m GVariant), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichGetUserValueMethodInfo a signature where
overloadedMethod = settingsSandwichGetUserValue
instance O.OverloadedMethodInfo SettingsSandwichGetUserValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichGetUserValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichGetUserValue"
})
#endif
foreign import ccall "dzl_settings_sandwich_get_value" dzl_settings_sandwich_get_value ::
Ptr SettingsSandwich ->
CString ->
IO (Ptr GVariant)
settingsSandwichGetValue ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> m GVariant
settingsSandwichGetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> m GVariant
settingsSandwichGetValue a
self Text
key = IO GVariant -> m GVariant
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
Ptr GVariant
result <- Ptr SettingsSandwich -> CString -> IO (Ptr GVariant)
dzl_settings_sandwich_get_value Ptr SettingsSandwich
self' CString
key'
Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingsSandwichGetValue" Ptr GVariant
result
GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.wrapGVariantPtr Ptr GVariant
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
GVariant -> IO GVariant
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichGetValueMethodInfo
instance (signature ~ (T.Text -> m GVariant), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichGetValueMethodInfo a signature where
overloadedMethod = settingsSandwichGetValue
instance O.OverloadedMethodInfo SettingsSandwichGetValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichGetValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichGetValue"
})
#endif
foreign import ccall "dzl_settings_sandwich_set_boolean" dzl_settings_sandwich_set_boolean ::
Ptr SettingsSandwich ->
CString ->
CInt ->
IO ()
settingsSandwichSetBoolean ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> Bool
-> m ()
settingsSandwichSetBoolean :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> Bool -> m ()
settingsSandwichSetBoolean a
self Text
key Bool
val = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
let val' :: CInt
val' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
val
Ptr SettingsSandwich -> CString -> CInt -> IO ()
dzl_settings_sandwich_set_boolean Ptr SettingsSandwich
self' CString
key' CInt
val'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichSetBooleanMethodInfo
instance (signature ~ (T.Text -> Bool -> m ()), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichSetBooleanMethodInfo a signature where
overloadedMethod = settingsSandwichSetBoolean
instance O.OverloadedMethodInfo SettingsSandwichSetBooleanMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichSetBoolean",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichSetBoolean"
})
#endif
foreign import ccall "dzl_settings_sandwich_set_double" dzl_settings_sandwich_set_double ::
Ptr SettingsSandwich ->
CString ->
CDouble ->
IO ()
settingsSandwichSetDouble ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> Double
-> m ()
settingsSandwichSetDouble :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> Double -> m ()
settingsSandwichSetDouble a
self Text
key Double
val = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
let val' :: CDouble
val' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
val
Ptr SettingsSandwich -> CString -> CDouble -> IO ()
dzl_settings_sandwich_set_double Ptr SettingsSandwich
self' CString
key' CDouble
val'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichSetDoubleMethodInfo
instance (signature ~ (T.Text -> Double -> m ()), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichSetDoubleMethodInfo a signature where
overloadedMethod = settingsSandwichSetDouble
instance O.OverloadedMethodInfo SettingsSandwichSetDoubleMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichSetDouble",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichSetDouble"
})
#endif
foreign import ccall "dzl_settings_sandwich_set_int" dzl_settings_sandwich_set_int ::
Ptr SettingsSandwich ->
CString ->
Int32 ->
IO ()
settingsSandwichSetInt ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> Int32
-> m ()
settingsSandwichSetInt :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> Int32 -> m ()
settingsSandwichSetInt a
self Text
key Int32
val = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
Ptr SettingsSandwich -> CString -> Int32 -> IO ()
dzl_settings_sandwich_set_int Ptr SettingsSandwich
self' CString
key' Int32
val
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichSetIntMethodInfo
instance (signature ~ (T.Text -> Int32 -> m ()), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichSetIntMethodInfo a signature where
overloadedMethod = settingsSandwichSetInt
instance O.OverloadedMethodInfo SettingsSandwichSetIntMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichSetInt",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichSetInt"
})
#endif
foreign import ccall "dzl_settings_sandwich_set_string" dzl_settings_sandwich_set_string ::
Ptr SettingsSandwich ->
CString ->
CString ->
IO ()
settingsSandwichSetString ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> T.Text
-> m ()
settingsSandwichSetString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> Text -> m ()
settingsSandwichSetString a
self Text
key Text
val = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
CString
val' <- Text -> IO CString
textToCString Text
val
Ptr SettingsSandwich -> CString -> CString -> IO ()
dzl_settings_sandwich_set_string Ptr SettingsSandwich
self' CString
key' CString
val'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
val'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichSetStringMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichSetStringMethodInfo a signature where
overloadedMethod = settingsSandwichSetString
instance O.OverloadedMethodInfo SettingsSandwichSetStringMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichSetString",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichSetString"
})
#endif
foreign import ccall "dzl_settings_sandwich_set_uint" dzl_settings_sandwich_set_uint ::
Ptr SettingsSandwich ->
CString ->
Word32 ->
IO ()
settingsSandwichSetUint ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> Word32
-> m ()
settingsSandwichSetUint :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> Word32 -> m ()
settingsSandwichSetUint a
self Text
key Word32
val = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
Ptr SettingsSandwich -> CString -> Word32 -> IO ()
dzl_settings_sandwich_set_uint Ptr SettingsSandwich
self' CString
key' Word32
val
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichSetUintMethodInfo
instance (signature ~ (T.Text -> Word32 -> m ()), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichSetUintMethodInfo a signature where
overloadedMethod = settingsSandwichSetUint
instance O.OverloadedMethodInfo SettingsSandwichSetUintMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichSetUint",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichSetUint"
})
#endif
foreign import ccall "dzl_settings_sandwich_set_value" dzl_settings_sandwich_set_value ::
Ptr SettingsSandwich ->
CString ->
Ptr GVariant ->
IO ()
settingsSandwichSetValue ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> GVariant
-> m ()
settingsSandwichSetValue :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> GVariant -> m ()
settingsSandwichSetValue a
self Text
key GVariant
value = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
key' <- Text -> IO CString
textToCString Text
key
Ptr GVariant
value' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
value
Ptr SettingsSandwich -> CString -> Ptr GVariant -> IO ()
dzl_settings_sandwich_set_value Ptr SettingsSandwich
self' CString
key' Ptr GVariant
value'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
value
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichSetValueMethodInfo
instance (signature ~ (T.Text -> GVariant -> m ()), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichSetValueMethodInfo a signature where
overloadedMethod = settingsSandwichSetValue
instance O.OverloadedMethodInfo SettingsSandwichSetValueMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichSetValue",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichSetValue"
})
#endif
foreign import ccall "dzl_settings_sandwich_unbind" dzl_settings_sandwich_unbind ::
Ptr SettingsSandwich ->
CString ->
IO ()
settingsSandwichUnbind ::
(B.CallStack.HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a
-> T.Text
-> m ()
settingsSandwichUnbind :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsSettingsSandwich a) =>
a -> Text -> m ()
settingsSandwichUnbind a
self Text
property = 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
Ptr SettingsSandwich
self' <- a -> IO (Ptr SettingsSandwich)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
CString
property' <- Text -> IO CString
textToCString Text
property
Ptr SettingsSandwich -> CString -> IO ()
dzl_settings_sandwich_unbind Ptr SettingsSandwich
self' CString
property'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
property'
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSandwichUnbindMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsSettingsSandwich a) => O.OverloadedMethod SettingsSandwichUnbindMethodInfo a signature where
overloadedMethod = settingsSandwichUnbind
instance O.OverloadedMethodInfo SettingsSandwichUnbindMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Dazzle.Objects.SettingsSandwich.settingsSandwichUnbind",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-dazzle-1.0.2/docs/GI-Dazzle-Objects-SettingsSandwich.html#v:settingsSandwichUnbind"
})
#endif