{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- This is an opaque structure type.  You may not access it directly.
-- 
-- /Since: 2.32/

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

module GI.Gio.Structs.SettingsSchemaSource
    ( 

-- * Exported types
    SettingsSchemaSource(..)                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [listSchemas]("GI.Gio.Structs.SettingsSchemaSource#g:method:listSchemas"), [lookup]("GI.Gio.Structs.SettingsSchemaSource#g:method:lookup"), [ref]("GI.Gio.Structs.SettingsSchemaSource#g:method:ref"), [unref]("GI.Gio.Structs.SettingsSchemaSource#g:method:unref").
-- 
-- ==== Getters
-- /None/.
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolveSettingsSchemaSourceMethod       ,
#endif

-- ** getDefault #method:getDefault#

    settingsSchemaSourceGetDefault          ,


-- ** listSchemas #method:listSchemas#

#if defined(ENABLE_OVERLOADING)
    SettingsSchemaSourceListSchemasMethodInfo,
#endif
    settingsSchemaSourceListSchemas         ,


-- ** lookup #method:lookup#

#if defined(ENABLE_OVERLOADING)
    SettingsSchemaSourceLookupMethodInfo    ,
#endif
    settingsSchemaSourceLookup              ,


-- ** newFromDirectory #method:newFromDirectory#

    settingsSchemaSourceNewFromDirectory    ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    SettingsSchemaSourceRefMethodInfo       ,
#endif
    settingsSchemaSourceRef                 ,


-- ** unref #method:unref#

#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.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import {-# SOURCE #-} qualified GI.Gio.Structs.SettingsSchema as Gio.SettingsSchema

-- | Memory-managed wrapper type.
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

-- | Convert 'SettingsSchemaSource' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe SettingsSchemaSource) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_settings_schema_source_get_type
    gvalueSet_ :: Ptr GValue -> Maybe SettingsSchemaSource -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SettingsSchemaSource
P.Nothing = Ptr GValue -> Ptr SettingsSchemaSource -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr SettingsSchemaSource
forall a. Ptr a
FP.nullPtr :: FP.Ptr SettingsSchemaSource)
    gvalueSet_ Ptr GValue
gv (P.Just SettingsSchemaSource
obj) = SettingsSchemaSource
-> (Ptr SettingsSchemaSource -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SettingsSchemaSource
obj (Ptr GValue -> Ptr SettingsSchemaSource -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe SettingsSchemaSource)
gvalueGet_ Ptr GValue
gv = do
        Ptr SettingsSchemaSource
ptr <- Ptr GValue -> IO (Ptr SettingsSchemaSource)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr SettingsSchemaSource)
        if Ptr SettingsSchemaSource
ptr Ptr SettingsSchemaSource -> Ptr SettingsSchemaSource -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr SettingsSchemaSource
forall a. Ptr a
FP.nullPtr
        then SettingsSchemaSource -> Maybe SettingsSchemaSource
forall a. a -> Maybe a
P.Just (SettingsSchemaSource -> Maybe SettingsSchemaSource)
-> IO SettingsSchemaSource -> IO (Maybe SettingsSchemaSource)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (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
        else Maybe SettingsSchemaSource -> IO (Maybe SettingsSchemaSource)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe SettingsSchemaSource
forall a. Maybe a
P.Nothing
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingsSchemaSource
type instance O.AttributeList SettingsSchemaSource = SettingsSchemaSourceAttributeList
type SettingsSchemaSourceAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method SettingsSchemaSource::new_from_directory
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "directory"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the filename of a directory"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "SettingsSchemaSource" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSettingsSchemaSource, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "trusted"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE, if the directory is trusted"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "SettingsSchemaSource" })
-- throws : True
-- Skip return : False

foreign import ccall "g_settings_schema_source_new_from_directory" g_settings_schema_source_new_from_directory :: 
    CString ->                              -- directory : TBasicType TFileName
    Ptr SettingsSchemaSource ->             -- parent : TInterface (Name {namespace = "Gio", name = "SettingsSchemaSource"})
    CInt ->                                 -- trusted : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr SettingsSchemaSource)

-- | Attempts to create a new schema source corresponding to the contents
-- of the given directory.
-- 
-- This function is not required for normal uses of t'GI.Gio.Objects.Settings.Settings' but it
-- may be useful to authors of plugin management systems.
-- 
-- The directory should contain a file called @gschemas.compiled@ as
-- produced by the [glib-compile-schemas][glib-compile-schemas] tool.
-- 
-- If /@trusted@/ is 'P.True' then @gschemas.compiled@ is trusted not to be
-- corrupted. This assumption has a performance advantage, but can result
-- in crashes or inconsistent behaviour in the case of a corrupted file.
-- Generally, you should set /@trusted@/ to 'P.True' for files installed by the
-- system and to 'P.False' for files in the home directory.
-- 
-- In either case, an empty file or some types of corruption in the file will
-- result in 'GI.GLib.Enums.FileErrorInval' being returned.
-- 
-- If /@parent@/ is non-'P.Nothing' then there are two effects.
-- 
-- First, if 'GI.Gio.Structs.SettingsSchemaSource.settingsSchemaSourceLookup' is called with the
-- /@recursive@/ flag set to 'P.True' and the schema can not be found in the
-- source, the lookup will recurse to the parent.
-- 
-- Second, any references to other schemas specified within this
-- source (ie: @child@ or @extends@) references may be resolved
-- from the /@parent@/.
-- 
-- For this second reason, except in very unusual situations, the
-- /@parent@/ should probably be given as the default schema source, as
-- returned by 'GI.Gio.Functions.settingsSchemaSourceGetDefault'.
-- 
-- /Since: 2.32/
settingsSchemaSourceNewFromDirectory ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@directory@/: the filename of a directory
    -> Maybe (SettingsSchemaSource)
    -- ^ /@parent@/: a t'GI.Gio.Structs.SettingsSchemaSource.SettingsSchemaSource', or 'P.Nothing'
    -> Bool
    -- ^ /@trusted@/: 'P.True', if the directory is trusted
    -> m SettingsSchemaSource
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
settingsSchemaSourceNewFromDirectory :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
[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

-- method SettingsSchemaSource::list_schemas
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "source"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "SettingsSchemaSource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSettingsSchemaSource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "recursive"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "if we should recurse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "non_relocatable"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the\n  list of non-relocatable schemas, in no defined order"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "relocatable"
--           , argType = TCArray True (-1) (-1) (TBasicType TUTF8)
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the list\n  of relocatable schemas, in no defined order"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_settings_schema_source_list_schemas" g_settings_schema_source_list_schemas :: 
    Ptr SettingsSchemaSource ->             -- source : TInterface (Name {namespace = "Gio", name = "SettingsSchemaSource"})
    CInt ->                                 -- recursive : TBasicType TBoolean
    Ptr (Ptr CString) ->                    -- non_relocatable : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr (Ptr CString) ->                    -- relocatable : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO ()

-- | Lists the schemas in a given source.
-- 
-- If /@recursive@/ is 'P.True' then include parent sources.  If 'P.False' then
-- only include the schemas from one source (ie: one directory).  You
-- probably want 'P.True'.
-- 
-- Non-relocatable schemas are those for which you can call
-- 'GI.Gio.Objects.Settings.settingsNew'.  Relocatable schemas are those for which you must
-- use 'GI.Gio.Objects.Settings.settingsNewWithPath'.
-- 
-- Do not call this function from normal programs.  This is designed for
-- use by database editors, commandline tools, etc.
-- 
-- /Since: 2.40/
settingsSchemaSourceListSchemas ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SettingsSchemaSource
    -- ^ /@source@/: a t'GI.Gio.Structs.SettingsSchemaSource.SettingsSchemaSource'
    -> Bool
    -- ^ /@recursive@/: if we should recurse
    -> m (([T.Text], [T.Text]))
settingsSchemaSourceListSchemas :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod SettingsSchemaSourceListSchemasMethodInfo SettingsSchemaSource signature where
    overloadedMethod = settingsSchemaSourceListSchemas

instance O.OverloadedMethodInfo SettingsSchemaSourceListSchemasMethodInfo SettingsSchemaSource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.SettingsSchemaSource.settingsSchemaSourceListSchemas",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-SettingsSchemaSource.html#v:settingsSchemaSourceListSchemas"
        })


#endif

-- method SettingsSchemaSource::lookup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "source"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "SettingsSchemaSource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSettingsSchemaSource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "schema_id"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a schema ID" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "recursive"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE if the lookup should be recursive"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "SettingsSchema" })
-- throws : False
-- Skip return : False

foreign import ccall "g_settings_schema_source_lookup" g_settings_schema_source_lookup :: 
    Ptr SettingsSchemaSource ->             -- source : TInterface (Name {namespace = "Gio", name = "SettingsSchemaSource"})
    CString ->                              -- schema_id : TBasicType TUTF8
    CInt ->                                 -- recursive : TBasicType TBoolean
    IO (Ptr Gio.SettingsSchema.SettingsSchema)

-- | Looks up a schema with the identifier /@schemaId@/ in /@source@/.
-- 
-- This function is not required for normal uses of t'GI.Gio.Objects.Settings.Settings' but it
-- may be useful to authors of plugin management systems or to those who
-- want to introspect the content of schemas.
-- 
-- If the schema isn\'t found directly in /@source@/ and /@recursive@/ is 'P.True'
-- then the parent sources will also be checked.
-- 
-- If the schema isn\'t found, 'P.Nothing' is returned.
-- 
-- /Since: 2.32/
settingsSchemaSourceLookup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SettingsSchemaSource
    -- ^ /@source@/: a t'GI.Gio.Structs.SettingsSchemaSource.SettingsSchemaSource'
    -> T.Text
    -- ^ /@schemaId@/: a schema ID
    -> Bool
    -- ^ /@recursive@/: 'P.True' if the lookup should be recursive
    -> m (Maybe Gio.SettingsSchema.SettingsSchema)
    -- ^ __Returns:__ a new t'GI.Gio.Structs.SettingsSchema.SettingsSchema'
settingsSchemaSourceLookup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod SettingsSchemaSourceLookupMethodInfo SettingsSchemaSource signature where
    overloadedMethod = settingsSchemaSourceLookup

instance O.OverloadedMethodInfo SettingsSchemaSourceLookupMethodInfo SettingsSchemaSource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.SettingsSchemaSource.settingsSchemaSourceLookup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-SettingsSchemaSource.html#v:settingsSchemaSourceLookup"
        })


#endif

-- method SettingsSchemaSource::ref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "source"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "SettingsSchemaSource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSettingsSchemaSource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "SettingsSchemaSource" })
-- throws : False
-- Skip return : False

foreign import ccall "g_settings_schema_source_ref" g_settings_schema_source_ref :: 
    Ptr SettingsSchemaSource ->             -- source : TInterface (Name {namespace = "Gio", name = "SettingsSchemaSource"})
    IO (Ptr SettingsSchemaSource)

-- | Increase the reference count of /@source@/, returning a new reference.
-- 
-- /Since: 2.32/
settingsSchemaSourceRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SettingsSchemaSource
    -- ^ /@source@/: a t'GI.Gio.Structs.SettingsSchemaSource.SettingsSchemaSource'
    -> m SettingsSchemaSource
    -- ^ __Returns:__ a new reference to /@source@/
settingsSchemaSourceRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod SettingsSchemaSourceRefMethodInfo SettingsSchemaSource signature where
    overloadedMethod = settingsSchemaSourceRef

instance O.OverloadedMethodInfo SettingsSchemaSourceRefMethodInfo SettingsSchemaSource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.SettingsSchemaSource.settingsSchemaSourceRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-SettingsSchemaSource.html#v:settingsSchemaSourceRef"
        })


#endif

-- method SettingsSchemaSource::unref
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "source"
--           , argType =
--               TInterface
--                 Name { namespace = "Gio" , name = "SettingsSchemaSource" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GSettingsSchemaSource"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_settings_schema_source_unref" g_settings_schema_source_unref :: 
    Ptr SettingsSchemaSource ->             -- source : TInterface (Name {namespace = "Gio", name = "SettingsSchemaSource"})
    IO ()

-- | Decrease the reference count of /@source@/, possibly freeing it.
-- 
-- /Since: 2.32/
settingsSchemaSourceUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    SettingsSchemaSource
    -- ^ /@source@/: a t'GI.Gio.Structs.SettingsSchemaSource.SettingsSchemaSource'
    -> m ()
settingsSchemaSourceUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod SettingsSchemaSourceUnrefMethodInfo SettingsSchemaSource signature where
    overloadedMethod = settingsSchemaSourceUnref

instance O.OverloadedMethodInfo SettingsSchemaSourceUnrefMethodInfo SettingsSchemaSource where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gio.Structs.SettingsSchemaSource.settingsSchemaSourceUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gio-2.0.29/docs/GI-Gio-Structs-SettingsSchemaSource.html#v:settingsSchemaSourceUnref"
        })


#endif

-- method SettingsSchemaSource::get_default
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Gio" , name = "SettingsSchemaSource" })
-- throws : False
-- Skip return : False

foreign import ccall "g_settings_schema_source_get_default" g_settings_schema_source_get_default :: 
    IO (Ptr SettingsSchemaSource)

-- | Gets the default system schema source.
-- 
-- This function is not required for normal uses of t'GI.Gio.Objects.Settings.Settings' but it
-- may be useful to authors of plugin management systems or to those who
-- want to introspect the content of schemas.
-- 
-- If no schemas are installed, 'P.Nothing' will be returned.
-- 
-- The returned source may actually consist of multiple schema sources
-- from different directories, depending on which directories were given
-- in @XDG_DATA_DIRS@ and @GSETTINGS_SCHEMA_DIR@. For this reason, all
-- lookups performed against the default source should probably be done
-- recursively.
-- 
-- /Since: 2.32/
settingsSchemaSourceGetDefault ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m (Maybe SettingsSchemaSource)
    -- ^ __Returns:__ the default schema source
settingsSchemaSourceGetDefault :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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.OverloadedMethod 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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveSettingsSchemaSourceMethod t SettingsSchemaSource, O.OverloadedMethod info SettingsSchemaSource p, R.HasField t SettingsSchemaSource p) => R.HasField t SettingsSchemaSource p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveSettingsSchemaSourceMethod t SettingsSchemaSource, O.OverloadedMethodInfo info SettingsSchemaSource) => OL.IsLabel t (O.MethodProxy info SettingsSchemaSource) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif