{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.SettingsSchema
(
SettingsSchema(..) ,
noSettingsSchema ,
#if defined(ENABLE_OVERLOADING)
ResolveSettingsSchemaMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
SettingsSchemaGetIdMethodInfo ,
#endif
settingsSchemaGetId ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaGetKeyMethodInfo ,
#endif
settingsSchemaGetKey ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaGetPathMethodInfo ,
#endif
settingsSchemaGetPath ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaHasKeyMethodInfo ,
#endif
settingsSchemaHasKey ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaListChildrenMethodInfo ,
#endif
settingsSchemaListChildren ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaListKeysMethodInfo ,
#endif
settingsSchemaListKeys ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaRefMethodInfo ,
#endif
settingsSchemaRef ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaUnrefMethodInfo ,
#endif
settingsSchemaUnref ,
) 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.ManagedPtr as B.ManagedPtr
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 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 {-# SOURCE #-} qualified GI.Gio.Structs.SettingsSchemaKey as Gio.SettingsSchemaKey
newtype SettingsSchema = SettingsSchema (ManagedPtr SettingsSchema)
deriving (SettingsSchema -> SettingsSchema -> Bool
(SettingsSchema -> SettingsSchema -> Bool)
-> (SettingsSchema -> SettingsSchema -> Bool) -> Eq SettingsSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SettingsSchema -> SettingsSchema -> Bool
$c/= :: SettingsSchema -> SettingsSchema -> Bool
== :: SettingsSchema -> SettingsSchema -> Bool
$c== :: SettingsSchema -> SettingsSchema -> Bool
Eq)
foreign import ccall "g_settings_schema_get_type" c_g_settings_schema_get_type ::
IO GType
instance BoxedObject SettingsSchema where
boxedType :: SettingsSchema -> IO GType
boxedType _ = IO GType
c_g_settings_schema_get_type
instance B.GValue.IsGValue SettingsSchema where
toGValue :: SettingsSchema -> IO GValue
toGValue o :: SettingsSchema
o = do
GType
gtype <- IO GType
c_g_settings_schema_get_type
SettingsSchema -> (Ptr SettingsSchema -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SettingsSchema
o (GType
-> (GValue -> Ptr SettingsSchema -> IO ())
-> Ptr SettingsSchema
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr SettingsSchema -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO SettingsSchema
fromGValue gv :: GValue
gv = do
Ptr SettingsSchema
ptr <- GValue -> IO (Ptr SettingsSchema)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr SettingsSchema)
(ManagedPtr SettingsSchema -> SettingsSchema)
-> Ptr SettingsSchema -> IO SettingsSchema
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr SettingsSchema -> SettingsSchema
SettingsSchema Ptr SettingsSchema
ptr
noSettingsSchema :: Maybe SettingsSchema
noSettingsSchema :: Maybe SettingsSchema
noSettingsSchema = Maybe SettingsSchema
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingsSchema
type instance O.AttributeList SettingsSchema = SettingsSchemaAttributeList
type SettingsSchemaAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "g_settings_schema_get_id" g_settings_schema_get_id ::
Ptr SettingsSchema ->
IO CString
settingsSchemaGetId ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchema
-> m T.Text
settingsSchemaGetId :: SettingsSchema -> m Text
settingsSchemaGetId schema :: SettingsSchema
schema = 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 SettingsSchema
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
CString
result <- Ptr SettingsSchema -> IO CString
g_settings_schema_get_id Ptr SettingsSchema
schema'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "settingsSchemaGetId" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
SettingsSchema -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchema
schema
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaGetIdMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo SettingsSchemaGetIdMethodInfo SettingsSchema signature where
overloadedMethod = settingsSchemaGetId
#endif
foreign import ccall "g_settings_schema_get_key" g_settings_schema_get_key ::
Ptr SettingsSchema ->
CString ->
IO (Ptr Gio.SettingsSchemaKey.SettingsSchemaKey)
settingsSchemaGetKey ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchema
-> T.Text
-> m Gio.SettingsSchemaKey.SettingsSchemaKey
settingsSchemaGetKey :: SettingsSchema -> Text -> m SettingsSchemaKey
settingsSchemaGetKey schema :: SettingsSchema
schema name :: Text
name = IO SettingsSchemaKey -> m SettingsSchemaKey
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingsSchemaKey -> m SettingsSchemaKey)
-> IO SettingsSchemaKey -> m SettingsSchemaKey
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSchema
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
CString
name' <- Text -> IO CString
textToCString Text
name
Ptr SettingsSchemaKey
result <- Ptr SettingsSchema -> CString -> IO (Ptr SettingsSchemaKey)
g_settings_schema_get_key Ptr SettingsSchema
schema' CString
name'
Text -> Ptr SettingsSchemaKey -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "settingsSchemaGetKey" Ptr SettingsSchemaKey
result
SettingsSchemaKey
result' <- ((ManagedPtr SettingsSchemaKey -> SettingsSchemaKey)
-> Ptr SettingsSchemaKey -> IO SettingsSchemaKey
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr SettingsSchemaKey -> SettingsSchemaKey
Gio.SettingsSchemaKey.SettingsSchemaKey) Ptr SettingsSchemaKey
result
SettingsSchema -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchema
schema
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
SettingsSchemaKey -> IO SettingsSchemaKey
forall (m :: * -> *) a. Monad m => a -> m a
return SettingsSchemaKey
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaGetKeyMethodInfo
instance (signature ~ (T.Text -> m Gio.SettingsSchemaKey.SettingsSchemaKey), MonadIO m) => O.MethodInfo SettingsSchemaGetKeyMethodInfo SettingsSchema signature where
overloadedMethod = settingsSchemaGetKey
#endif
foreign import ccall "g_settings_schema_get_path" g_settings_schema_get_path ::
Ptr SettingsSchema ->
IO CString
settingsSchemaGetPath ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchema
-> m T.Text
settingsSchemaGetPath :: SettingsSchema -> m Text
settingsSchemaGetPath schema :: SettingsSchema
schema = 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 SettingsSchema
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
CString
result <- Ptr SettingsSchema -> IO CString
g_settings_schema_get_path Ptr SettingsSchema
schema'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "settingsSchemaGetPath" CString
result
Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
SettingsSchema -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchema
schema
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaGetPathMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo SettingsSchemaGetPathMethodInfo SettingsSchema signature where
overloadedMethod = settingsSchemaGetPath
#endif
foreign import ccall "g_settings_schema_has_key" g_settings_schema_has_key ::
Ptr SettingsSchema ->
CString ->
IO CInt
settingsSchemaHasKey ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchema
-> T.Text
-> m Bool
settingsSchemaHasKey :: SettingsSchema -> Text -> m Bool
settingsSchemaHasKey schema :: SettingsSchema
schema name :: Text
name = IO Bool -> m Bool
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 SettingsSchema
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
CString
name' <- Text -> IO CString
textToCString Text
name
CInt
result <- Ptr SettingsSchema -> CString -> IO CInt
g_settings_schema_has_key Ptr SettingsSchema
schema' CString
name'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
SettingsSchema -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchema
schema
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
name'
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaHasKeyMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.MethodInfo SettingsSchemaHasKeyMethodInfo SettingsSchema signature where
overloadedMethod = settingsSchemaHasKey
#endif
foreign import ccall "g_settings_schema_list_children" g_settings_schema_list_children ::
Ptr SettingsSchema ->
IO (Ptr CString)
settingsSchemaListChildren ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchema
-> m [T.Text]
settingsSchemaListChildren :: SettingsSchema -> m [Text]
settingsSchemaListChildren schema :: SettingsSchema
schema = 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 SettingsSchema
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
Ptr CString
result <- Ptr SettingsSchema -> IO (Ptr CString)
g_settings_schema_list_children Ptr SettingsSchema
schema'
Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "settingsSchemaListChildren" Ptr CString
result
[Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
SettingsSchema -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchema
schema
[Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaListChildrenMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m) => O.MethodInfo SettingsSchemaListChildrenMethodInfo SettingsSchema signature where
overloadedMethod = settingsSchemaListChildren
#endif
foreign import ccall "g_settings_schema_list_keys" g_settings_schema_list_keys ::
Ptr SettingsSchema ->
IO (Ptr CString)
settingsSchemaListKeys ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchema
-> m [T.Text]
settingsSchemaListKeys :: SettingsSchema -> m [Text]
settingsSchemaListKeys schema :: SettingsSchema
schema = 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 SettingsSchema
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
Ptr CString
result <- Ptr SettingsSchema -> IO (Ptr CString)
g_settings_schema_list_keys Ptr SettingsSchema
schema'
Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "settingsSchemaListKeys" Ptr CString
result
[Text]
result' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
result
(CString -> IO ()) -> Ptr CString -> IO ()
forall a b. (Ptr a -> IO b) -> Ptr (Ptr a) -> IO ()
mapZeroTerminatedCArray CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
result
SettingsSchema -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchema
schema
[Text] -> IO [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return [Text]
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaListKeysMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m) => O.MethodInfo SettingsSchemaListKeysMethodInfo SettingsSchema signature where
overloadedMethod = settingsSchemaListKeys
#endif
foreign import ccall "g_settings_schema_ref" g_settings_schema_ref ::
Ptr SettingsSchema ->
IO (Ptr SettingsSchema)
settingsSchemaRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchema
-> m SettingsSchema
settingsSchemaRef :: SettingsSchema -> m SettingsSchema
settingsSchemaRef schema :: SettingsSchema
schema = IO SettingsSchema -> m SettingsSchema
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingsSchema -> m SettingsSchema)
-> IO SettingsSchema -> m SettingsSchema
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSchema
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
Ptr SettingsSchema
result <- Ptr SettingsSchema -> IO (Ptr SettingsSchema)
g_settings_schema_ref Ptr SettingsSchema
schema'
Text -> Ptr SettingsSchema -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "settingsSchemaRef" Ptr SettingsSchema
result
SettingsSchema
result' <- ((ManagedPtr SettingsSchema -> SettingsSchema)
-> Ptr SettingsSchema -> IO SettingsSchema
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr SettingsSchema -> SettingsSchema
SettingsSchema) Ptr SettingsSchema
result
SettingsSchema -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchema
schema
SettingsSchema -> IO SettingsSchema
forall (m :: * -> *) a. Monad m => a -> m a
return SettingsSchema
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaRefMethodInfo
instance (signature ~ (m SettingsSchema), MonadIO m) => O.MethodInfo SettingsSchemaRefMethodInfo SettingsSchema signature where
overloadedMethod = settingsSchemaRef
#endif
foreign import ccall "g_settings_schema_unref" g_settings_schema_unref ::
Ptr SettingsSchema ->
IO ()
settingsSchemaUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchema
-> m ()
settingsSchemaUnref :: SettingsSchema -> m ()
settingsSchemaUnref schema :: SettingsSchema
schema = 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 SettingsSchema
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
Ptr SettingsSchema -> IO ()
g_settings_schema_unref Ptr SettingsSchema
schema'
SettingsSchema -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchema
schema
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo SettingsSchemaUnrefMethodInfo SettingsSchema signature where
overloadedMethod = settingsSchemaUnref
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveSettingsSchemaMethod (t :: Symbol) (o :: *) :: * where
ResolveSettingsSchemaMethod "hasKey" o = SettingsSchemaHasKeyMethodInfo
ResolveSettingsSchemaMethod "listChildren" o = SettingsSchemaListChildrenMethodInfo
ResolveSettingsSchemaMethod "listKeys" o = SettingsSchemaListKeysMethodInfo
ResolveSettingsSchemaMethod "ref" o = SettingsSchemaRefMethodInfo
ResolveSettingsSchemaMethod "unref" o = SettingsSchemaUnrefMethodInfo
ResolveSettingsSchemaMethod "getId" o = SettingsSchemaGetIdMethodInfo
ResolveSettingsSchemaMethod "getKey" o = SettingsSchemaGetKeyMethodInfo
ResolveSettingsSchemaMethod "getPath" o = SettingsSchemaGetPathMethodInfo
ResolveSettingsSchemaMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSettingsSchemaMethod t SettingsSchema, O.MethodInfo info SettingsSchema p) => OL.IsLabel t (SettingsSchema -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif