{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.SettingsSchemaSource
(
SettingsSchemaSource(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveSettingsSchemaSourceMethod ,
#endif
settingsSchemaSourceGetDefault ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaSourceListSchemasMethodInfo,
#endif
settingsSchemaSourceListSchemas ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaSourceLookupMethodInfo ,
#endif
settingsSchemaSourceLookup ,
settingsSchemaSourceNewFromDirectory ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaSourceRefMethodInfo ,
#endif
settingsSchemaSourceRef ,
#if defined(ENABLE_OVERLOADING)
SettingsSchemaSourceUnrefMethodInfo ,
#endif
settingsSchemaSourceUnref ,
) 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.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 {-# SOURCE #-} qualified GI.Gio.Structs.SettingsSchema as Gio.SettingsSchema
newtype SettingsSchemaSource = SettingsSchemaSource (SP.ManagedPtr SettingsSchemaSource)
deriving (SettingsSchemaSource -> SettingsSchemaSource -> Bool
(SettingsSchemaSource -> SettingsSchemaSource -> Bool)
-> (SettingsSchemaSource -> SettingsSchemaSource -> Bool)
-> Eq SettingsSchemaSource
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SettingsSchemaSource -> SettingsSchemaSource -> Bool
$c/= :: SettingsSchemaSource -> SettingsSchemaSource -> Bool
== :: SettingsSchemaSource -> SettingsSchemaSource -> Bool
$c== :: SettingsSchemaSource -> SettingsSchemaSource -> Bool
Eq)
instance SP.ManagedPtrNewtype SettingsSchemaSource where
toManagedPtr :: SettingsSchemaSource -> ManagedPtr SettingsSchemaSource
toManagedPtr (SettingsSchemaSource ManagedPtr SettingsSchemaSource
p) = ManagedPtr SettingsSchemaSource
p
foreign import ccall "g_settings_schema_source_get_type" c_g_settings_schema_source_get_type ::
IO GType
type instance O.ParentTypes SettingsSchemaSource = '[]
instance O.HasParentTypes SettingsSchemaSource
instance B.Types.TypedObject SettingsSchemaSource where
glibType :: IO GType
glibType = IO GType
c_g_settings_schema_source_get_type
instance B.Types.GBoxed SettingsSchemaSource
instance B.GValue.IsGValue SettingsSchemaSource where
toGValue :: SettingsSchemaSource -> IO GValue
toGValue SettingsSchemaSource
o = do
GType
gtype <- IO GType
c_g_settings_schema_source_get_type
SettingsSchemaSource
-> (Ptr SettingsSchemaSource -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SettingsSchemaSource
o (GType
-> (GValue -> Ptr SettingsSchemaSource -> IO ())
-> Ptr SettingsSchemaSource
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr SettingsSchemaSource -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO SettingsSchemaSource
fromGValue GValue
gv = do
Ptr SettingsSchemaSource
ptr <- GValue -> IO (Ptr SettingsSchemaSource)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr SettingsSchemaSource)
(ManagedPtr SettingsSchemaSource -> SettingsSchemaSource)
-> Ptr SettingsSchemaSource -> IO SettingsSchemaSource
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr SettingsSchemaSource -> SettingsSchemaSource
SettingsSchemaSource Ptr SettingsSchemaSource
ptr
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingsSchemaSource
type instance O.AttributeList SettingsSchemaSource = SettingsSchemaSourceAttributeList
type SettingsSchemaSourceAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "g_settings_schema_source_new_from_directory" g_settings_schema_source_new_from_directory ::
CString ->
Ptr SettingsSchemaSource ->
CInt ->
Ptr (Ptr GError) ->
IO (Ptr SettingsSchemaSource)
settingsSchemaSourceNewFromDirectory ::
(B.CallStack.HasCallStack, MonadIO m) =>
[Char]
-> Maybe (SettingsSchemaSource)
-> Bool
-> m SettingsSchemaSource
settingsSchemaSourceNewFromDirectory :: [Char]
-> Maybe SettingsSchemaSource -> Bool -> m SettingsSchemaSource
settingsSchemaSourceNewFromDirectory [Char]
directory Maybe SettingsSchemaSource
parent Bool
trusted = IO SettingsSchemaSource -> m SettingsSchemaSource
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingsSchemaSource -> m SettingsSchemaSource)
-> IO SettingsSchemaSource -> m SettingsSchemaSource
forall a b. (a -> b) -> a -> b
$ do
CString
directory' <- [Char] -> IO CString
stringToCString [Char]
directory
Ptr SettingsSchemaSource
maybeParent <- case Maybe SettingsSchemaSource
parent of
Maybe SettingsSchemaSource
Nothing -> Ptr SettingsSchemaSource -> IO (Ptr SettingsSchemaSource)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SettingsSchemaSource
forall a. Ptr a
nullPtr
Just SettingsSchemaSource
jParent -> do
Ptr SettingsSchemaSource
jParent' <- SettingsSchemaSource -> IO (Ptr SettingsSchemaSource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchemaSource
jParent
Ptr SettingsSchemaSource -> IO (Ptr SettingsSchemaSource)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr SettingsSchemaSource
jParent'
let trusted' :: CInt
trusted' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
trusted
IO SettingsSchemaSource -> IO () -> IO SettingsSchemaSource
forall a b. IO a -> IO b -> IO a
onException (do
Ptr SettingsSchemaSource
result <- (Ptr (Ptr GError) -> IO (Ptr SettingsSchemaSource))
-> IO (Ptr SettingsSchemaSource)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr SettingsSchemaSource))
-> IO (Ptr SettingsSchemaSource))
-> (Ptr (Ptr GError) -> IO (Ptr SettingsSchemaSource))
-> IO (Ptr SettingsSchemaSource)
forall a b. (a -> b) -> a -> b
$ CString
-> Ptr SettingsSchemaSource
-> CInt
-> Ptr (Ptr GError)
-> IO (Ptr SettingsSchemaSource)
g_settings_schema_source_new_from_directory CString
directory' Ptr SettingsSchemaSource
maybeParent CInt
trusted'
Text -> Ptr SettingsSchemaSource -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingsSchemaSourceNewFromDirectory" Ptr SettingsSchemaSource
result
SettingsSchemaSource
result' <- ((ManagedPtr SettingsSchemaSource -> SettingsSchemaSource)
-> Ptr SettingsSchemaSource -> IO SettingsSchemaSource
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr SettingsSchemaSource -> SettingsSchemaSource
SettingsSchemaSource) Ptr SettingsSchemaSource
result
Maybe SettingsSchemaSource
-> (SettingsSchemaSource -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe SettingsSchemaSource
parent SettingsSchemaSource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
directory'
SettingsSchemaSource -> IO SettingsSchemaSource
forall (m :: * -> *) a. Monad m => a -> m a
return SettingsSchemaSource
result'
) (do
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
directory'
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_settings_schema_source_list_schemas" g_settings_schema_source_list_schemas ::
Ptr SettingsSchemaSource ->
CInt ->
Ptr (Ptr CString) ->
Ptr (Ptr CString) ->
IO ()
settingsSchemaSourceListSchemas ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchemaSource
-> Bool
-> m (([T.Text], [T.Text]))
settingsSchemaSourceListSchemas :: SettingsSchemaSource -> Bool -> m ([Text], [Text])
settingsSchemaSourceListSchemas SettingsSchemaSource
source Bool
recursive = IO ([Text], [Text]) -> m ([Text], [Text])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], [Text]) -> m ([Text], [Text]))
-> IO ([Text], [Text]) -> m ([Text], [Text])
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSchemaSource
source' <- SettingsSchemaSource -> IO (Ptr SettingsSchemaSource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchemaSource
source
let recursive' :: CInt
recursive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
recursive
Ptr (Ptr CString)
nonRelocatable <- IO (Ptr (Ptr CString))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr CString))
Ptr (Ptr CString)
relocatable <- IO (Ptr (Ptr CString))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr CString))
Ptr SettingsSchemaSource
-> CInt -> Ptr (Ptr CString) -> Ptr (Ptr CString) -> IO ()
g_settings_schema_source_list_schemas Ptr SettingsSchemaSource
source' CInt
recursive' Ptr (Ptr CString)
nonRelocatable Ptr (Ptr CString)
relocatable
Ptr CString
nonRelocatable' <- Ptr (Ptr CString) -> IO (Ptr CString)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CString)
nonRelocatable
[Text]
nonRelocatable'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
nonRelocatable'
(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
nonRelocatable'
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
nonRelocatable'
Ptr CString
relocatable' <- Ptr (Ptr CString) -> IO (Ptr CString)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr CString)
relocatable
[Text]
relocatable'' <- HasCallStack => Ptr CString -> IO [Text]
Ptr CString -> IO [Text]
unpackZeroTerminatedUTF8CArray Ptr CString
relocatable'
(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
relocatable'
Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
relocatable'
SettingsSchemaSource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchemaSource
source
Ptr (Ptr CString) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CString)
nonRelocatable
Ptr (Ptr CString) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr CString)
relocatable
([Text], [Text]) -> IO ([Text], [Text])
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text]
nonRelocatable'', [Text]
relocatable'')
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaSourceListSchemasMethodInfo
instance (signature ~ (Bool -> m (([T.Text], [T.Text]))), MonadIO m) => O.MethodInfo SettingsSchemaSourceListSchemasMethodInfo SettingsSchemaSource signature where
overloadedMethod = settingsSchemaSourceListSchemas
#endif
foreign import ccall "g_settings_schema_source_lookup" g_settings_schema_source_lookup ::
Ptr SettingsSchemaSource ->
CString ->
CInt ->
IO (Ptr Gio.SettingsSchema.SettingsSchema)
settingsSchemaSourceLookup ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchemaSource
-> T.Text
-> Bool
-> m (Maybe Gio.SettingsSchema.SettingsSchema)
settingsSchemaSourceLookup :: SettingsSchemaSource -> Text -> Bool -> m (Maybe SettingsSchema)
settingsSchemaSourceLookup SettingsSchemaSource
source Text
schemaId Bool
recursive = IO (Maybe SettingsSchema) -> m (Maybe SettingsSchema)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe SettingsSchema) -> m (Maybe SettingsSchema))
-> IO (Maybe SettingsSchema) -> m (Maybe SettingsSchema)
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSchemaSource
source' <- SettingsSchemaSource -> IO (Ptr SettingsSchemaSource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchemaSource
source
CString
schemaId' <- Text -> IO CString
textToCString Text
schemaId
let recursive' :: CInt
recursive' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
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
fromEnum) Bool
recursive
Ptr SettingsSchema
result <- Ptr SettingsSchemaSource
-> CString -> CInt -> IO (Ptr SettingsSchema)
g_settings_schema_source_lookup Ptr SettingsSchemaSource
source' CString
schemaId' CInt
recursive'
Maybe SettingsSchema
maybeResult <- Ptr SettingsSchema
-> (Ptr SettingsSchema -> IO SettingsSchema)
-> IO (Maybe SettingsSchema)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr SettingsSchema
result ((Ptr SettingsSchema -> IO SettingsSchema)
-> IO (Maybe SettingsSchema))
-> (Ptr SettingsSchema -> IO SettingsSchema)
-> IO (Maybe SettingsSchema)
forall a b. (a -> b) -> a -> b
$ \Ptr SettingsSchema
result' -> do
SettingsSchema
result'' <- ((ManagedPtr SettingsSchema -> SettingsSchema)
-> Ptr SettingsSchema -> IO SettingsSchema
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr SettingsSchema -> SettingsSchema
Gio.SettingsSchema.SettingsSchema) Ptr SettingsSchema
result'
SettingsSchema -> IO SettingsSchema
forall (m :: * -> *) a. Monad m => a -> m a
return SettingsSchema
result''
SettingsSchemaSource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchemaSource
source
CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
schemaId'
Maybe SettingsSchema -> IO (Maybe SettingsSchema)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SettingsSchema
maybeResult
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaSourceLookupMethodInfo
instance (signature ~ (T.Text -> Bool -> m (Maybe Gio.SettingsSchema.SettingsSchema)), MonadIO m) => O.MethodInfo SettingsSchemaSourceLookupMethodInfo SettingsSchemaSource signature where
overloadedMethod = settingsSchemaSourceLookup
#endif
foreign import ccall "g_settings_schema_source_ref" g_settings_schema_source_ref ::
Ptr SettingsSchemaSource ->
IO (Ptr SettingsSchemaSource)
settingsSchemaSourceRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchemaSource
-> m SettingsSchemaSource
settingsSchemaSourceRef :: SettingsSchemaSource -> m SettingsSchemaSource
settingsSchemaSourceRef SettingsSchemaSource
source = IO SettingsSchemaSource -> m SettingsSchemaSource
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SettingsSchemaSource -> m SettingsSchemaSource)
-> IO SettingsSchemaSource -> m SettingsSchemaSource
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSchemaSource
source' <- SettingsSchemaSource -> IO (Ptr SettingsSchemaSource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchemaSource
source
Ptr SettingsSchemaSource
result <- Ptr SettingsSchemaSource -> IO (Ptr SettingsSchemaSource)
g_settings_schema_source_ref Ptr SettingsSchemaSource
source'
Text -> Ptr SettingsSchemaSource -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"settingsSchemaSourceRef" Ptr SettingsSchemaSource
result
SettingsSchemaSource
result' <- ((ManagedPtr SettingsSchemaSource -> SettingsSchemaSource)
-> Ptr SettingsSchemaSource -> IO SettingsSchemaSource
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr SettingsSchemaSource -> SettingsSchemaSource
SettingsSchemaSource) Ptr SettingsSchemaSource
result
SettingsSchemaSource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchemaSource
source
SettingsSchemaSource -> IO SettingsSchemaSource
forall (m :: * -> *) a. Monad m => a -> m a
return SettingsSchemaSource
result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaSourceRefMethodInfo
instance (signature ~ (m SettingsSchemaSource), MonadIO m) => O.MethodInfo SettingsSchemaSourceRefMethodInfo SettingsSchemaSource signature where
overloadedMethod = settingsSchemaSourceRef
#endif
foreign import ccall "g_settings_schema_source_unref" g_settings_schema_source_unref ::
Ptr SettingsSchemaSource ->
IO ()
settingsSchemaSourceUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
SettingsSchemaSource
-> m ()
settingsSchemaSourceUnref :: SettingsSchemaSource -> m ()
settingsSchemaSourceUnref SettingsSchemaSource
source = 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 SettingsSchemaSource
source' <- SettingsSchemaSource -> IO (Ptr SettingsSchemaSource)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchemaSource
source
Ptr SettingsSchemaSource -> IO ()
g_settings_schema_source_unref Ptr SettingsSchemaSource
source'
SettingsSchemaSource -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr SettingsSchemaSource
source
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaSourceUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo SettingsSchemaSourceUnrefMethodInfo SettingsSchemaSource signature where
overloadedMethod = settingsSchemaSourceUnref
#endif
foreign import ccall "g_settings_schema_source_get_default" g_settings_schema_source_get_default ::
IO (Ptr SettingsSchemaSource)
settingsSchemaSourceGetDefault ::
(B.CallStack.HasCallStack, MonadIO m) =>
m (Maybe SettingsSchemaSource)
settingsSchemaSourceGetDefault :: m (Maybe SettingsSchemaSource)
settingsSchemaSourceGetDefault = IO (Maybe SettingsSchemaSource) -> m (Maybe SettingsSchemaSource)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe SettingsSchemaSource) -> m (Maybe SettingsSchemaSource))
-> IO (Maybe SettingsSchemaSource)
-> m (Maybe SettingsSchemaSource)
forall a b. (a -> b) -> a -> b
$ do
Ptr SettingsSchemaSource
result <- IO (Ptr SettingsSchemaSource)
g_settings_schema_source_get_default
Maybe SettingsSchemaSource
maybeResult <- Ptr SettingsSchemaSource
-> (Ptr SettingsSchemaSource -> IO SettingsSchemaSource)
-> IO (Maybe SettingsSchemaSource)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr SettingsSchemaSource
result ((Ptr SettingsSchemaSource -> IO SettingsSchemaSource)
-> IO (Maybe SettingsSchemaSource))
-> (Ptr SettingsSchemaSource -> IO SettingsSchemaSource)
-> IO (Maybe SettingsSchemaSource)
forall a b. (a -> b) -> a -> b
$ \Ptr SettingsSchemaSource
result' -> do
SettingsSchemaSource
result'' <- ((ManagedPtr SettingsSchemaSource -> SettingsSchemaSource)
-> Ptr SettingsSchemaSource -> IO SettingsSchemaSource
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr SettingsSchemaSource -> SettingsSchemaSource
SettingsSchemaSource) Ptr SettingsSchemaSource
result'
SettingsSchemaSource -> IO SettingsSchemaSource
forall (m :: * -> *) a. Monad m => a -> m a
return SettingsSchemaSource
result''
Maybe SettingsSchemaSource -> IO (Maybe SettingsSchemaSource)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SettingsSchemaSource
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveSettingsSchemaSourceMethod (t :: Symbol) (o :: *) :: * where
ResolveSettingsSchemaSourceMethod "listSchemas" o = SettingsSchemaSourceListSchemasMethodInfo
ResolveSettingsSchemaSourceMethod "lookup" o = SettingsSchemaSourceLookupMethodInfo
ResolveSettingsSchemaSourceMethod "ref" o = SettingsSchemaSourceRefMethodInfo
ResolveSettingsSchemaSourceMethod "unref" o = SettingsSchemaSourceUnrefMethodInfo
ResolveSettingsSchemaSourceMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveSettingsSchemaSourceMethod t SettingsSchemaSource, O.MethodInfo info SettingsSchemaSource p) => OL.IsLabel t (SettingsSchemaSource -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif