{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gio.Structs.SettingsSchema
(
SettingsSchema(..) ,
#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.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.GLib.Structs.VariantType as GLib.VariantType
import {-# SOURCE #-} qualified GI.Gio.Structs.SettingsSchemaKey as Gio.SettingsSchemaKey
#else
import {-# SOURCE #-} qualified GI.Gio.Structs.SettingsSchemaKey as Gio.SettingsSchemaKey
#endif
newtype SettingsSchema = SettingsSchema (SP.ManagedPtr SettingsSchema)
deriving (SettingsSchema -> SettingsSchema -> Bool
(SettingsSchema -> SettingsSchema -> Bool)
-> (SettingsSchema -> SettingsSchema -> Bool) -> Eq SettingsSchema
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SettingsSchema -> SettingsSchema -> Bool
== :: SettingsSchema -> SettingsSchema -> Bool
$c/= :: SettingsSchema -> SettingsSchema -> Bool
/= :: SettingsSchema -> SettingsSchema -> Bool
Eq)
instance SP.ManagedPtrNewtype SettingsSchema where
toManagedPtr :: SettingsSchema -> ManagedPtr SettingsSchema
toManagedPtr (SettingsSchema ManagedPtr SettingsSchema
p) = ManagedPtr SettingsSchema
p
foreign import ccall "g_settings_schema_get_type" c_g_settings_schema_get_type ::
IO GType
type instance O.ParentTypes SettingsSchema = '[]
instance O.HasParentTypes SettingsSchema
instance B.Types.TypedObject SettingsSchema where
glibType :: IO GType
glibType = IO GType
c_g_settings_schema_get_type
instance B.Types.GBoxed SettingsSchema
instance B.GValue.IsGValue (Maybe SettingsSchema) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_settings_schema_get_type
gvalueSet_ :: Ptr GValue -> Maybe SettingsSchema -> IO ()
gvalueSet_ Ptr GValue
gv Maybe SettingsSchema
P.Nothing = Ptr GValue -> Ptr SettingsSchema -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr SettingsSchema
forall a. Ptr a
FP.nullPtr :: FP.Ptr SettingsSchema)
gvalueSet_ Ptr GValue
gv (P.Just SettingsSchema
obj) = SettingsSchema -> (Ptr SettingsSchema -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr SettingsSchema
obj (Ptr GValue -> Ptr SettingsSchema -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe SettingsSchema)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr SettingsSchema)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr SettingsSchema)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newBoxed SettingsSchema ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList SettingsSchema
type instance O.AttributeList SettingsSchema = SettingsSchemaAttributeList
type SettingsSchemaAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m Text
settingsSchemaGetId SettingsSchema
schema = 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
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
result <- g_settings_schema_get_id schema'
checkUnexpectedReturnNULL "settingsSchemaGetId" result
result' <- cstringToText result
touchManagedPtr schema
return result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaGetIdMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod SettingsSchemaGetIdMethodInfo SettingsSchema signature where
overloadedMethod :: SettingsSchema -> signature
overloadedMethod = SettingsSchema -> signature
SettingsSchema -> m Text
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m Text
settingsSchemaGetId
instance O.OverloadedMethodInfo SettingsSchemaGetIdMethodInfo SettingsSchema where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.SettingsSchema.settingsSchemaGetId",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-SettingsSchema.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> Text -> m SettingsSchemaKey
settingsSchemaGetKey SettingsSchema
schema Text
name = IO SettingsSchemaKey -> m SettingsSchemaKey
forall a. IO a -> m a
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
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
name' <- textToCString name
result <- g_settings_schema_get_key schema' name'
checkUnexpectedReturnNULL "settingsSchemaGetKey" result
result' <- (wrapBoxed Gio.SettingsSchemaKey.SettingsSchemaKey) result
touchManagedPtr schema
freeMem name'
return result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaGetKeyMethodInfo
instance (signature ~ (T.Text -> m Gio.SettingsSchemaKey.SettingsSchemaKey), MonadIO m) => O.OverloadedMethod SettingsSchemaGetKeyMethodInfo SettingsSchema signature where
overloadedMethod :: SettingsSchema -> signature
overloadedMethod = SettingsSchema -> signature
SettingsSchema -> Text -> m SettingsSchemaKey
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> Text -> m SettingsSchemaKey
settingsSchemaGetKey
instance O.OverloadedMethodInfo SettingsSchemaGetKeyMethodInfo SettingsSchema where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.SettingsSchema.settingsSchemaGetKey",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-SettingsSchema.html#v: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 (Maybe T.Text)
settingsSchemaGetPath :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m (Maybe Text)
settingsSchemaGetPath SettingsSchema
schema = IO (Maybe Text) -> m (Maybe Text)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ do
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
result <- g_settings_schema_get_path schema'
maybeResult <- convertIfNonNull result $ \CString
result' -> do
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
return result''
touchManagedPtr schema
return maybeResult
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaGetPathMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod SettingsSchemaGetPathMethodInfo SettingsSchema signature where
overloadedMethod :: SettingsSchema -> signature
overloadedMethod = SettingsSchema -> signature
SettingsSchema -> m (Maybe Text)
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m (Maybe Text)
settingsSchemaGetPath
instance O.OverloadedMethodInfo SettingsSchemaGetPathMethodInfo SettingsSchema where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.SettingsSchema.settingsSchemaGetPath",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-SettingsSchema.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> Text -> m Bool
settingsSchemaHasKey SettingsSchema
schema Text
name = 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
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
name' <- textToCString name
result <- g_settings_schema_has_key schema' name'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr schema
freeMem name'
return result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaHasKeyMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.OverloadedMethod SettingsSchemaHasKeyMethodInfo SettingsSchema signature where
overloadedMethod :: SettingsSchema -> signature
overloadedMethod = SettingsSchema -> signature
SettingsSchema -> Text -> m Bool
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> Text -> m Bool
settingsSchemaHasKey
instance O.OverloadedMethodInfo SettingsSchemaHasKeyMethodInfo SettingsSchema where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.SettingsSchema.settingsSchemaHasKey",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-SettingsSchema.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m [Text]
settingsSchemaListChildren SettingsSchema
schema = 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
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
result <- g_settings_schema_list_children schema'
checkUnexpectedReturnNULL "settingsSchemaListChildren" result
result' <- unpackZeroTerminatedUTF8CArray result
mapZeroTerminatedCArray freeMem result
freeMem result
touchManagedPtr schema
return result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaListChildrenMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m) => O.OverloadedMethod SettingsSchemaListChildrenMethodInfo SettingsSchema signature where
overloadedMethod :: SettingsSchema -> signature
overloadedMethod = SettingsSchema -> signature
SettingsSchema -> m [Text]
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m [Text]
settingsSchemaListChildren
instance O.OverloadedMethodInfo SettingsSchemaListChildrenMethodInfo SettingsSchema where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.SettingsSchema.settingsSchemaListChildren",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-SettingsSchema.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m [Text]
settingsSchemaListKeys SettingsSchema
schema = 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
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
result <- g_settings_schema_list_keys schema'
checkUnexpectedReturnNULL "settingsSchemaListKeys" result
result' <- unpackZeroTerminatedUTF8CArray result
mapZeroTerminatedCArray freeMem result
freeMem result
touchManagedPtr schema
return result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaListKeysMethodInfo
instance (signature ~ (m [T.Text]), MonadIO m) => O.OverloadedMethod SettingsSchemaListKeysMethodInfo SettingsSchema signature where
overloadedMethod :: SettingsSchema -> signature
overloadedMethod = SettingsSchema -> signature
SettingsSchema -> m [Text]
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m [Text]
settingsSchemaListKeys
instance O.OverloadedMethodInfo SettingsSchemaListKeysMethodInfo SettingsSchema where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.SettingsSchema.settingsSchemaListKeys",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-SettingsSchema.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m SettingsSchema
settingsSchemaRef SettingsSchema
schema = IO SettingsSchema -> m SettingsSchema
forall a. IO a -> m a
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
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
result <- g_settings_schema_ref schema'
checkUnexpectedReturnNULL "settingsSchemaRef" result
result' <- (wrapBoxed SettingsSchema) result
touchManagedPtr schema
return result'
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaRefMethodInfo
instance (signature ~ (m SettingsSchema), MonadIO m) => O.OverloadedMethod SettingsSchemaRefMethodInfo SettingsSchema signature where
overloadedMethod :: SettingsSchema -> signature
overloadedMethod = SettingsSchema -> signature
SettingsSchema -> m SettingsSchema
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m SettingsSchema
settingsSchemaRef
instance O.OverloadedMethodInfo SettingsSchemaRefMethodInfo SettingsSchema where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.SettingsSchema.settingsSchemaRef",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-SettingsSchema.html#v: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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m ()
settingsSchemaUnref SettingsSchema
schema = 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
schema' <- SettingsSchema -> IO (Ptr SettingsSchema)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr SettingsSchema
schema
g_settings_schema_unref schema'
touchManagedPtr schema
return ()
#if defined(ENABLE_OVERLOADING)
data SettingsSchemaUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod SettingsSchemaUnrefMethodInfo SettingsSchema signature where
overloadedMethod :: SettingsSchema -> signature
overloadedMethod = SettingsSchema -> signature
SettingsSchema -> m ()
forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
SettingsSchema -> m ()
settingsSchemaUnref
instance O.OverloadedMethodInfo SettingsSchemaUnrefMethodInfo SettingsSchema where
overloadedMethodInfo :: Maybe ResolvedSymbolInfo
overloadedMethodInfo = ResolvedSymbolInfo -> Maybe ResolvedSymbolInfo
forall a. a -> Maybe a
P.Just (O.ResolvedSymbolInfo {
resolvedSymbolName :: Text
O.resolvedSymbolName = Text
"GI.Gio.Structs.SettingsSchema.settingsSchemaUnref",
resolvedSymbolURL :: Text
O.resolvedSymbolURL = Text
"https://hackage.haskell.org/package/gi-gio-2.0.38/docs/GI-Gio-Structs-SettingsSchema.html#v:settingsSchemaUnref"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveSettingsSchemaMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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.OverloadedMethod info SettingsSchema p) => OL.IsLabel t (SettingsSchema -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: SettingsSchema -> p
fromLabel = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveSettingsSchemaMethod t SettingsSchema, O.OverloadedMethod info SettingsSchema p, R.HasField t SettingsSchema p) => R.HasField t SettingsSchema p where
getField :: SettingsSchema -> p
getField = forall {k} (i :: k) o s. OverloadedMethod i o s => o -> s
forall i o s. OverloadedMethod i o s => o -> s
O.overloadedMethod @info
#endif
instance (info ~ ResolveSettingsSchemaMethod t SettingsSchema, O.OverloadedMethodInfo info SettingsSchema) => OL.IsLabel t (O.MethodProxy info SettingsSchema) where
#if MIN_VERSION_base(4,10,0)
fromLabel :: MethodProxy info SettingsSchema
fromLabel = MethodProxy info SettingsSchema
forall info obj. MethodProxy info obj
O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif