{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The GKeyFile struct contains only private data
-- and should not be accessed directly.

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

module GI.GLib.Structs.KeyFile
    ( 

-- * Exported types
    KeyFile(..)                             ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [hasGroup]("GI.GLib.Structs.KeyFile#g:method:hasGroup"), [loadFromBytes]("GI.GLib.Structs.KeyFile#g:method:loadFromBytes"), [loadFromData]("GI.GLib.Structs.KeyFile#g:method:loadFromData"), [loadFromDataDirs]("GI.GLib.Structs.KeyFile#g:method:loadFromDataDirs"), [loadFromDirs]("GI.GLib.Structs.KeyFile#g:method:loadFromDirs"), [loadFromFile]("GI.GLib.Structs.KeyFile#g:method:loadFromFile"), [removeComment]("GI.GLib.Structs.KeyFile#g:method:removeComment"), [removeGroup]("GI.GLib.Structs.KeyFile#g:method:removeGroup"), [removeKey]("GI.GLib.Structs.KeyFile#g:method:removeKey"), [saveToFile]("GI.GLib.Structs.KeyFile#g:method:saveToFile"), [toData]("GI.GLib.Structs.KeyFile#g:method:toData"), [unref]("GI.GLib.Structs.KeyFile#g:method:unref").
-- 
-- ==== Getters
-- [getBoolean]("GI.GLib.Structs.KeyFile#g:method:getBoolean"), [getBooleanList]("GI.GLib.Structs.KeyFile#g:method:getBooleanList"), [getComment]("GI.GLib.Structs.KeyFile#g:method:getComment"), [getDouble]("GI.GLib.Structs.KeyFile#g:method:getDouble"), [getDoubleList]("GI.GLib.Structs.KeyFile#g:method:getDoubleList"), [getGroups]("GI.GLib.Structs.KeyFile#g:method:getGroups"), [getInt64]("GI.GLib.Structs.KeyFile#g:method:getInt64"), [getInteger]("GI.GLib.Structs.KeyFile#g:method:getInteger"), [getIntegerList]("GI.GLib.Structs.KeyFile#g:method:getIntegerList"), [getKeys]("GI.GLib.Structs.KeyFile#g:method:getKeys"), [getLocaleForKey]("GI.GLib.Structs.KeyFile#g:method:getLocaleForKey"), [getLocaleString]("GI.GLib.Structs.KeyFile#g:method:getLocaleString"), [getLocaleStringList]("GI.GLib.Structs.KeyFile#g:method:getLocaleStringList"), [getStartGroup]("GI.GLib.Structs.KeyFile#g:method:getStartGroup"), [getString]("GI.GLib.Structs.KeyFile#g:method:getString"), [getStringList]("GI.GLib.Structs.KeyFile#g:method:getStringList"), [getUint64]("GI.GLib.Structs.KeyFile#g:method:getUint64"), [getValue]("GI.GLib.Structs.KeyFile#g:method:getValue").
-- 
-- ==== Setters
-- [setBoolean]("GI.GLib.Structs.KeyFile#g:method:setBoolean"), [setBooleanList]("GI.GLib.Structs.KeyFile#g:method:setBooleanList"), [setComment]("GI.GLib.Structs.KeyFile#g:method:setComment"), [setDouble]("GI.GLib.Structs.KeyFile#g:method:setDouble"), [setDoubleList]("GI.GLib.Structs.KeyFile#g:method:setDoubleList"), [setInt64]("GI.GLib.Structs.KeyFile#g:method:setInt64"), [setInteger]("GI.GLib.Structs.KeyFile#g:method:setInteger"), [setIntegerList]("GI.GLib.Structs.KeyFile#g:method:setIntegerList"), [setListSeparator]("GI.GLib.Structs.KeyFile#g:method:setListSeparator"), [setLocaleString]("GI.GLib.Structs.KeyFile#g:method:setLocaleString"), [setLocaleStringList]("GI.GLib.Structs.KeyFile#g:method:setLocaleStringList"), [setString]("GI.GLib.Structs.KeyFile#g:method:setString"), [setStringList]("GI.GLib.Structs.KeyFile#g:method:setStringList"), [setUint64]("GI.GLib.Structs.KeyFile#g:method:setUint64"), [setValue]("GI.GLib.Structs.KeyFile#g:method:setValue").

#if defined(ENABLE_OVERLOADING)
    ResolveKeyFileMethod                    ,
#endif

-- ** errorQuark #method:errorQuark#

    keyFileErrorQuark                       ,


-- ** getBoolean #method:getBoolean#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetBooleanMethodInfo             ,
#endif
    keyFileGetBoolean                       ,


-- ** getBooleanList #method:getBooleanList#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetBooleanListMethodInfo         ,
#endif
    keyFileGetBooleanList                   ,


-- ** getComment #method:getComment#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetCommentMethodInfo             ,
#endif
    keyFileGetComment                       ,


-- ** getDouble #method:getDouble#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetDoubleMethodInfo              ,
#endif
    keyFileGetDouble                        ,


-- ** getDoubleList #method:getDoubleList#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetDoubleListMethodInfo          ,
#endif
    keyFileGetDoubleList                    ,


-- ** getGroups #method:getGroups#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetGroupsMethodInfo              ,
#endif
    keyFileGetGroups                        ,


-- ** getInt64 #method:getInt64#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetInt64MethodInfo               ,
#endif
    keyFileGetInt64                         ,


-- ** getInteger #method:getInteger#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetIntegerMethodInfo             ,
#endif
    keyFileGetInteger                       ,


-- ** getIntegerList #method:getIntegerList#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetIntegerListMethodInfo         ,
#endif
    keyFileGetIntegerList                   ,


-- ** getKeys #method:getKeys#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetKeysMethodInfo                ,
#endif
    keyFileGetKeys                          ,


-- ** getLocaleForKey #method:getLocaleForKey#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetLocaleForKeyMethodInfo        ,
#endif
    keyFileGetLocaleForKey                  ,


-- ** getLocaleString #method:getLocaleString#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetLocaleStringMethodInfo        ,
#endif
    keyFileGetLocaleString                  ,


-- ** getLocaleStringList #method:getLocaleStringList#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetLocaleStringListMethodInfo    ,
#endif
    keyFileGetLocaleStringList              ,


-- ** getStartGroup #method:getStartGroup#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetStartGroupMethodInfo          ,
#endif
    keyFileGetStartGroup                    ,


-- ** getString #method:getString#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetStringMethodInfo              ,
#endif
    keyFileGetString                        ,


-- ** getStringList #method:getStringList#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetStringListMethodInfo          ,
#endif
    keyFileGetStringList                    ,


-- ** getUint64 #method:getUint64#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetUint64MethodInfo              ,
#endif
    keyFileGetUint64                        ,


-- ** getValue #method:getValue#

#if defined(ENABLE_OVERLOADING)
    KeyFileGetValueMethodInfo               ,
#endif
    keyFileGetValue                         ,


-- ** hasGroup #method:hasGroup#

#if defined(ENABLE_OVERLOADING)
    KeyFileHasGroupMethodInfo               ,
#endif
    keyFileHasGroup                         ,


-- ** loadFromBytes #method:loadFromBytes#

#if defined(ENABLE_OVERLOADING)
    KeyFileLoadFromBytesMethodInfo          ,
#endif
    keyFileLoadFromBytes                    ,


-- ** loadFromData #method:loadFromData#

#if defined(ENABLE_OVERLOADING)
    KeyFileLoadFromDataMethodInfo           ,
#endif
    keyFileLoadFromData                     ,


-- ** loadFromDataDirs #method:loadFromDataDirs#

#if defined(ENABLE_OVERLOADING)
    KeyFileLoadFromDataDirsMethodInfo       ,
#endif
    keyFileLoadFromDataDirs                 ,


-- ** loadFromDirs #method:loadFromDirs#

#if defined(ENABLE_OVERLOADING)
    KeyFileLoadFromDirsMethodInfo           ,
#endif
    keyFileLoadFromDirs                     ,


-- ** loadFromFile #method:loadFromFile#

#if defined(ENABLE_OVERLOADING)
    KeyFileLoadFromFileMethodInfo           ,
#endif
    keyFileLoadFromFile                     ,


-- ** new #method:new#

    keyFileNew                              ,


-- ** removeComment #method:removeComment#

#if defined(ENABLE_OVERLOADING)
    KeyFileRemoveCommentMethodInfo          ,
#endif
    keyFileRemoveComment                    ,


-- ** removeGroup #method:removeGroup#

#if defined(ENABLE_OVERLOADING)
    KeyFileRemoveGroupMethodInfo            ,
#endif
    keyFileRemoveGroup                      ,


-- ** removeKey #method:removeKey#

#if defined(ENABLE_OVERLOADING)
    KeyFileRemoveKeyMethodInfo              ,
#endif
    keyFileRemoveKey                        ,


-- ** saveToFile #method:saveToFile#

#if defined(ENABLE_OVERLOADING)
    KeyFileSaveToFileMethodInfo             ,
#endif
    keyFileSaveToFile                       ,


-- ** setBoolean #method:setBoolean#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetBooleanMethodInfo             ,
#endif
    keyFileSetBoolean                       ,


-- ** setBooleanList #method:setBooleanList#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetBooleanListMethodInfo         ,
#endif
    keyFileSetBooleanList                   ,


-- ** setComment #method:setComment#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetCommentMethodInfo             ,
#endif
    keyFileSetComment                       ,


-- ** setDouble #method:setDouble#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetDoubleMethodInfo              ,
#endif
    keyFileSetDouble                        ,


-- ** setDoubleList #method:setDoubleList#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetDoubleListMethodInfo          ,
#endif
    keyFileSetDoubleList                    ,


-- ** setInt64 #method:setInt64#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetInt64MethodInfo               ,
#endif
    keyFileSetInt64                         ,


-- ** setInteger #method:setInteger#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetIntegerMethodInfo             ,
#endif
    keyFileSetInteger                       ,


-- ** setIntegerList #method:setIntegerList#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetIntegerListMethodInfo         ,
#endif
    keyFileSetIntegerList                   ,


-- ** setListSeparator #method:setListSeparator#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetListSeparatorMethodInfo       ,
#endif
    keyFileSetListSeparator                 ,


-- ** setLocaleString #method:setLocaleString#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetLocaleStringMethodInfo        ,
#endif
    keyFileSetLocaleString                  ,


-- ** setLocaleStringList #method:setLocaleStringList#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetLocaleStringListMethodInfo    ,
#endif
    keyFileSetLocaleStringList              ,


-- ** setString #method:setString#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetStringMethodInfo              ,
#endif
    keyFileSetString                        ,


-- ** setStringList #method:setStringList#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetStringListMethodInfo          ,
#endif
    keyFileSetStringList                    ,


-- ** setUint64 #method:setUint64#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetUint64MethodInfo              ,
#endif
    keyFileSetUint64                        ,


-- ** setValue #method:setValue#

#if defined(ENABLE_OVERLOADING)
    KeyFileSetValueMethodInfo               ,
#endif
    keyFileSetValue                         ,


-- ** toData #method:toData#

#if defined(ENABLE_OVERLOADING)
    KeyFileToDataMethodInfo                 ,
#endif
    keyFileToData                           ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    KeyFileUnrefMethodInfo                  ,
#endif
    keyFileUnref                            ,




    ) 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 {-# SOURCE #-} qualified GI.GLib.Flags as GLib.Flags
import {-# SOURCE #-} qualified GI.GLib.Structs.Bytes as GLib.Bytes

-- | Memory-managed wrapper type.
newtype KeyFile = KeyFile (SP.ManagedPtr KeyFile)
    deriving (KeyFile -> KeyFile -> Bool
(KeyFile -> KeyFile -> Bool)
-> (KeyFile -> KeyFile -> Bool) -> Eq KeyFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeyFile -> KeyFile -> Bool
== :: KeyFile -> KeyFile -> Bool
$c/= :: KeyFile -> KeyFile -> Bool
/= :: KeyFile -> KeyFile -> Bool
Eq)

instance SP.ManagedPtrNewtype KeyFile where
    toManagedPtr :: KeyFile -> ManagedPtr KeyFile
toManagedPtr (KeyFile ManagedPtr KeyFile
p) = ManagedPtr KeyFile
p

foreign import ccall "g_key_file_get_type" c_g_key_file_get_type :: 
    IO GType

type instance O.ParentTypes KeyFile = '[]
instance O.HasParentTypes KeyFile

instance B.Types.TypedObject KeyFile where
    glibType :: IO GType
glibType = IO GType
c_g_key_file_get_type

instance B.Types.GBoxed KeyFile

-- | Convert 'KeyFile' 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 KeyFile) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_g_key_file_get_type
    gvalueSet_ :: Ptr GValue -> Maybe KeyFile -> IO ()
gvalueSet_ Ptr GValue
gv Maybe KeyFile
P.Nothing = Ptr GValue -> Ptr KeyFile -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr KeyFile
forall a. Ptr a
FP.nullPtr :: FP.Ptr KeyFile)
    gvalueSet_ Ptr GValue
gv (P.Just KeyFile
obj) = KeyFile -> (Ptr KeyFile -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr KeyFile
obj (Ptr GValue -> Ptr KeyFile -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe KeyFile)
gvalueGet_ Ptr GValue
gv = do
        Ptr KeyFile
ptr <- Ptr GValue -> IO (Ptr KeyFile)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr KeyFile)
        if Ptr KeyFile
ptr Ptr KeyFile -> Ptr KeyFile -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr KeyFile
forall a. Ptr a
FP.nullPtr
        then KeyFile -> Maybe KeyFile
forall a. a -> Maybe a
P.Just (KeyFile -> Maybe KeyFile) -> IO KeyFile -> IO (Maybe KeyFile)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr KeyFile -> KeyFile) -> Ptr KeyFile -> IO KeyFile
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr KeyFile -> KeyFile
KeyFile Ptr KeyFile
ptr
        else Maybe KeyFile -> IO (Maybe KeyFile)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe KeyFile
forall a. Maybe a
P.Nothing
        
    


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList KeyFile
type instance O.AttributeList KeyFile = KeyFileAttributeList
type KeyFileAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

-- method KeyFile::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "KeyFile" })
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_new" g_key_file_new :: 
    IO (Ptr KeyFile)

-- | Creates a new empty t'GI.GLib.Structs.KeyFile.KeyFile' object. Use
-- 'GI.GLib.Structs.KeyFile.keyFileLoadFromFile', 'GI.GLib.Structs.KeyFile.keyFileLoadFromData',
-- 'GI.GLib.Structs.KeyFile.keyFileLoadFromDirs' or 'GI.GLib.Structs.KeyFile.keyFileLoadFromDataDirs' to
-- read an existing key file.
-- 
-- /Since: 2.6/
keyFileNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m KeyFile
    -- ^ __Returns:__ an empty t'GI.GLib.Structs.KeyFile.KeyFile'.
keyFileNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m KeyFile
keyFileNew  = IO KeyFile -> m KeyFile
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO KeyFile -> m KeyFile) -> IO KeyFile -> m KeyFile
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
result <- IO (Ptr KeyFile)
g_key_file_new
    Text -> Ptr KeyFile -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileNew" Ptr KeyFile
result
    KeyFile
result' <- ((ManagedPtr KeyFile -> KeyFile) -> Ptr KeyFile -> IO KeyFile
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr KeyFile -> KeyFile
KeyFile) Ptr KeyFile
result
    KeyFile -> IO KeyFile
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return KeyFile
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method KeyFile::get_boolean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_boolean" g_key_file_get_boolean :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Returns the value associated with /@key@/ under /@groupName@/ as a
-- boolean.
-- 
-- If /@key@/ cannot be found then 'P.False' is returned and /@error@/ is set
-- to 'GI.GLib.Enums.KeyFileErrorKeyNotFound'. Likewise, if the value
-- associated with /@key@/ cannot be interpreted as a boolean then 'P.False'
-- is returned and /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorInvalidValue'.
-- 
-- /Since: 2.6/
keyFileGetBoolean ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetBoolean :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m ()
keyFileGetBoolean KeyFile
keyFile Text
groupName Text
key = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO CInt
g_key_file_get_boolean Ptr KeyFile
keyFile' CString
groupName' CString
key'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetBooleanMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m) => O.OverloadedMethod KeyFileGetBooleanMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetBoolean

instance O.OverloadedMethodInfo KeyFileGetBooleanMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetBoolean",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetBoolean"
        })


#endif

-- method KeyFile::get_boolean_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of booleans returned"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of booleans returned"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 3 (TBasicType TBoolean))
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_boolean_list" g_key_file_get_boolean_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CInt)

-- | Returns the values associated with /@key@/ under /@groupName@/ as
-- booleans.
-- 
-- If /@key@/ cannot be found then 'P.Nothing' is returned and /@error@/ is set to
-- 'GI.GLib.Enums.KeyFileErrorKeyNotFound'. Likewise, if the values associated
-- with /@key@/ cannot be interpreted as booleans then 'P.Nothing' is returned
-- and /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorInvalidValue'.
-- 
-- /Since: 2.6/
keyFileGetBooleanList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> m [Bool]
    -- ^ __Returns:__ 
    --    the values associated with the key as a list of booleans, or 'P.Nothing' if the
    --    key was not found or could not be parsed. The returned list of booleans
    --    should be freed with 'GI.GLib.Functions.free' when no longer needed. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetBooleanList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m [Bool]
keyFileGetBooleanList KeyFile
keyFile Text
groupName Text
key = IO [Bool] -> m [Bool]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Bool] -> m [Bool]) -> IO [Bool] -> m [Bool]
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO [Bool] -> IO () -> IO [Bool]
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CInt
result <- (Ptr (Ptr GError) -> IO (Ptr CInt)) -> IO (Ptr CInt)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CInt)) -> IO (Ptr CInt))
-> (Ptr (Ptr GError) -> IO (Ptr CInt)) -> IO (Ptr CInt)
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString
-> CString
-> Ptr Word64
-> Ptr (Ptr GError)
-> IO (Ptr CInt)
g_key_file_get_boolean_list Ptr KeyFile
keyFile' CString
groupName' CString
key' Ptr Word64
length_
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        Text -> Ptr CInt -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetBooleanList" Ptr CInt
result
        [Bool]
result' <- ((CInt -> Bool) -> Word64 -> Ptr CInt -> IO [Bool]
forall a b c.
(Integral a, Storable b) =>
(b -> c) -> a -> Ptr b -> IO [c]
unpackMapStorableArrayWithLength (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) Word64
length_') Ptr CInt
result
        Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        [Bool] -> IO [Bool]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Bool]
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetBooleanListMethodInfo
instance (signature ~ (T.Text -> T.Text -> m [Bool]), MonadIO m) => O.OverloadedMethod KeyFileGetBooleanListMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetBooleanList

instance O.OverloadedMethodInfo KeyFileGetBooleanListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetBooleanList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetBooleanList"
        })


#endif

-- method KeyFile::get_comment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_comment" g_key_file_get_comment :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | Retrieves a comment above /@key@/ from /@groupName@/.
-- If /@key@/ is 'P.Nothing' then /@comment@/ will be read from above
-- /@groupName@/. If both /@key@/ and /@groupName@/ are 'P.Nothing', then
-- /@comment@/ will be read from above the first group in the file.
-- 
-- Note that the returned string does not include the \'#\' comment markers,
-- but does include any whitespace after them (on each line). It includes
-- the line breaks between lines, but does not include the final line break.
-- 
-- /Since: 2.6/
keyFileGetComment ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> Maybe (T.Text)
    -- ^ /@groupName@/: a group name, or 'P.Nothing'
    -> Maybe (T.Text)
    -- ^ /@key@/: a key
    -> m T.Text
    -- ^ __Returns:__ a comment that should be freed with 'GI.GLib.Functions.free' /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetComment :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Maybe Text -> Maybe Text -> m Text
keyFileGetComment KeyFile
keyFile Maybe Text
groupName Maybe Text
key = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
maybeGroupName <- case Maybe Text
groupName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jGroupName -> do
            CString
jGroupName' <- Text -> IO CString
textToCString Text
jGroupName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGroupName'
    CString
maybeKey <- case Maybe Text
key of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jKey -> do
            CString
jKey' <- Text -> IO CString
textToCString Text
jKey
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jKey'
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO CString
g_key_file_get_comment Ptr KeyFile
keyFile' CString
maybeGroupName CString
maybeKey
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetComment" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeKey
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeKey
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetCommentMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (T.Text) -> m T.Text), MonadIO m) => O.OverloadedMethod KeyFileGetCommentMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetComment

instance O.OverloadedMethodInfo KeyFileGetCommentMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetComment",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetComment"
        })


#endif

-- method KeyFile::get_double
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_double" g_key_file_get_double :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CDouble

-- | Returns the value associated with /@key@/ under /@groupName@/ as a
-- double. If /@groupName@/ is 'P.Nothing', the start_group is used.
-- 
-- If /@key@/ cannot be found then 0.0 is returned and /@error@/ is set to
-- 'GI.GLib.Enums.KeyFileErrorKeyNotFound'. Likewise, if the value associated
-- with /@key@/ cannot be interpreted as a double then 0.0 is returned
-- and /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorInvalidValue'.
-- 
-- /Since: 2.12/
keyFileGetDouble ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> m Double
    -- ^ __Returns:__ the value associated with the key as a double, or
    --     0.0 if the key was not found or could not be parsed. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetDouble :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m Double
keyFileGetDouble KeyFile
keyFile Text
groupName Text
key = IO Double -> m Double
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    IO Double -> IO () -> IO Double
forall a b. IO a -> IO b -> IO a
onException (do
        CDouble
result <- (Ptr (Ptr GError) -> IO CDouble) -> IO CDouble
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CDouble) -> IO CDouble)
-> (Ptr (Ptr GError) -> IO CDouble) -> IO CDouble
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO CDouble
g_key_file_get_double Ptr KeyFile
keyFile' CString
groupName' CString
key'
        let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Double -> IO Double
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetDoubleMethodInfo
instance (signature ~ (T.Text -> T.Text -> m Double), MonadIO m) => O.OverloadedMethod KeyFileGetDoubleMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetDouble

instance O.OverloadedMethodInfo KeyFileGetDoubleMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetDouble",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetDouble"
        })


#endif

-- method KeyFile::get_double_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of doubles returned"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of doubles returned"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 3 (TBasicType TDouble))
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_double_list" g_key_file_get_double_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CDouble)

-- | Returns the values associated with /@key@/ under /@groupName@/ as
-- doubles.
-- 
-- If /@key@/ cannot be found then 'P.Nothing' is returned and /@error@/ is set to
-- 'GI.GLib.Enums.KeyFileErrorKeyNotFound'. Likewise, if the values associated
-- with /@key@/ cannot be interpreted as doubles then 'P.Nothing' is returned
-- and /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorInvalidValue'.
-- 
-- /Since: 2.12/
keyFileGetDoubleList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> m [Double]
    -- ^ __Returns:__ 
    --     the values associated with the key as a list of doubles, or 'P.Nothing' if the
    --     key was not found or could not be parsed. The returned list of doubles
    --     should be freed with 'GI.GLib.Functions.free' when no longer needed. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetDoubleList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m [Double]
keyFileGetDoubleList KeyFile
keyFile Text
groupName Text
key = IO [Double] -> m [Double]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Double] -> m [Double]) -> IO [Double] -> m [Double]
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO [Double] -> IO () -> IO [Double]
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CDouble
result <- (Ptr (Ptr GError) -> IO (Ptr CDouble)) -> IO (Ptr CDouble)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CDouble)) -> IO (Ptr CDouble))
-> (Ptr (Ptr GError) -> IO (Ptr CDouble)) -> IO (Ptr CDouble)
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString
-> CString
-> Ptr Word64
-> Ptr (Ptr GError)
-> IO (Ptr CDouble)
g_key_file_get_double_list Ptr KeyFile
keyFile' CString
groupName' CString
key' Ptr Word64
length_
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        Text -> Ptr CDouble -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetDoubleList" Ptr CDouble
result
        [Double]
result' <- ((CDouble -> Double) -> Word64 -> Ptr CDouble -> IO [Double]
forall a b c.
(Integral a, Storable b) =>
(b -> c) -> a -> Ptr b -> IO [c]
unpackMapStorableArrayWithLength CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Word64
length_') Ptr CDouble
result
        Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        [Double] -> IO [Double]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Double]
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetDoubleListMethodInfo
instance (signature ~ (T.Text -> T.Text -> m [Double]), MonadIO m) => O.OverloadedMethod KeyFileGetDoubleListMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetDoubleList

instance O.OverloadedMethodInfo KeyFileGetDoubleListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetDoubleList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetDoubleList"
        })


#endif

-- method KeyFile::get_groups
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the number of returned groups, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_get_groups" g_key_file_get_groups :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    IO (Ptr CString)

-- | Returns all groups in the key file loaded with /@keyFile@/.
-- The array of returned groups will be 'P.Nothing'-terminated, so
-- /@length@/ may optionally be 'P.Nothing'.
-- 
-- /Since: 2.6/
keyFileGetGroups ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> m (([T.Text], Word64))
    -- ^ __Returns:__ a newly-allocated 'P.Nothing'-terminated array of strings.
    --   Use 'GI.GLib.Functions.strfreev' to free it.
keyFileGetGroups :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> m ([Text], Word64)
keyFileGetGroups KeyFile
keyFile = IO ([Text], Word64) -> m ([Text], Word64)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], Word64) -> m ([Text], Word64))
-> IO ([Text], Word64) -> m ([Text], Word64)
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    Ptr CString
result <- Ptr KeyFile -> Ptr Word64 -> IO (Ptr CString)
g_key_file_get_groups Ptr KeyFile
keyFile' Ptr Word64
length_
    Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetGroups" 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
    Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
    ([Text], Word64) -> IO ([Text], Word64)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text]
result', Word64
length_')

#if defined(ENABLE_OVERLOADING)
data KeyFileGetGroupsMethodInfo
instance (signature ~ (m (([T.Text], Word64))), MonadIO m) => O.OverloadedMethod KeyFileGetGroupsMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetGroups

instance O.OverloadedMethodInfo KeyFileGetGroupsMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetGroups",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetGroups"
        })


#endif

-- method KeyFile::get_int64
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a non-%NULL #GKeyFile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a non-%NULL group name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a non-%NULL key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt64)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_int64" g_key_file_get_int64 :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO Int64

-- | Returns the value associated with /@key@/ under /@groupName@/ as a signed
-- 64-bit integer. This is similar to 'GI.GLib.Structs.KeyFile.keyFileGetInteger' but can return
-- 64-bit results without truncation.
-- 
-- /Since: 2.26/
keyFileGetInt64 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a non-'P.Nothing' t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a non-'P.Nothing' group name
    -> T.Text
    -- ^ /@key@/: a non-'P.Nothing' key
    -> m Int64
    -- ^ __Returns:__ the value associated with the key as a signed 64-bit integer, or
    -- 0 if the key was not found or could not be parsed. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetInt64 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m Int64
keyFileGetInt64 KeyFile
keyFile Text
groupName Text
key = IO Int64 -> m Int64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int64 -> m Int64) -> IO Int64 -> m Int64
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    IO Int64 -> IO () -> IO Int64
forall a b. IO a -> IO b -> IO a
onException (do
        Int64
result <- (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int64) -> IO Int64)
-> (Ptr (Ptr GError) -> IO Int64) -> IO Int64
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO Int64
g_key_file_get_int64 Ptr KeyFile
keyFile' CString
groupName' CString
key'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Int64 -> IO Int64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetInt64MethodInfo
instance (signature ~ (T.Text -> T.Text -> m Int64), MonadIO m) => O.OverloadedMethod KeyFileGetInt64MethodInfo KeyFile signature where
    overloadedMethod = keyFileGetInt64

instance O.OverloadedMethodInfo KeyFileGetInt64MethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetInt64",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetInt64"
        })


#endif

-- method KeyFile::get_integer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_integer" g_key_file_get_integer :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO Int32

-- | Returns the value associated with /@key@/ under /@groupName@/ as an
-- integer.
-- 
-- If /@key@/ cannot be found then 0 is returned and /@error@/ is set to
-- 'GI.GLib.Enums.KeyFileErrorKeyNotFound'. Likewise, if the value associated
-- with /@key@/ cannot be interpreted as an integer, or is out of range
-- for a @/gint/@, then 0 is returned
-- and /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorInvalidValue'.
-- 
-- /Since: 2.6/
keyFileGetInteger ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> m Int32
    -- ^ __Returns:__ the value associated with the key as an integer, or
    --     0 if the key was not found or could not be parsed. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetInteger :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m Int32
keyFileGetInteger KeyFile
keyFile Text
groupName Text
key = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    IO Int32 -> IO () -> IO Int32
forall a b. IO a -> IO b -> IO a
onException (do
        Int32
result <- (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Int32) -> IO Int32)
-> (Ptr (Ptr GError) -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO Int32
g_key_file_get_integer Ptr KeyFile
keyFile' CString
groupName' CString
key'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Int32 -> IO Int32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetIntegerMethodInfo
instance (signature ~ (T.Text -> T.Text -> m Int32), MonadIO m) => O.OverloadedMethod KeyFileGetIntegerMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetInteger

instance O.OverloadedMethodInfo KeyFileGetIntegerMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetInteger",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetInteger"
        })


#endif

-- method KeyFile::get_integer_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of integers returned"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the number of integers returned"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just (TCArray False (-1) 3 (TBasicType TInt))
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_integer_list" g_key_file_get_integer_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Int32)

-- | Returns the values associated with /@key@/ under /@groupName@/ as
-- integers.
-- 
-- If /@key@/ cannot be found then 'P.Nothing' is returned and /@error@/ is set to
-- 'GI.GLib.Enums.KeyFileErrorKeyNotFound'. Likewise, if the values associated
-- with /@key@/ cannot be interpreted as integers, or are out of range for
-- @/gint/@, then 'P.Nothing' is returned
-- and /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorInvalidValue'.
-- 
-- /Since: 2.6/
keyFileGetIntegerList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> m [Int32]
    -- ^ __Returns:__ 
    --     the values associated with the key as a list of integers, or 'P.Nothing' if
    --     the key was not found or could not be parsed. The returned list of
    --     integers should be freed with 'GI.GLib.Functions.free' when no longer needed. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetIntegerList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m [Int32]
keyFileGetIntegerList KeyFile
keyFile Text
groupName Text
key = IO [Int32] -> m [Int32]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Int32] -> m [Int32]) -> IO [Int32] -> m [Int32]
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO [Int32] -> IO () -> IO [Int32]
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Int32
result <- (Ptr (Ptr GError) -> IO (Ptr Int32)) -> IO (Ptr Int32)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Int32)) -> IO (Ptr Int32))
-> (Ptr (Ptr GError) -> IO (Ptr Int32)) -> IO (Ptr Int32)
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString
-> CString
-> Ptr Word64
-> Ptr (Ptr GError)
-> IO (Ptr Int32)
g_key_file_get_integer_list Ptr KeyFile
keyFile' CString
groupName' CString
key' Ptr Word64
length_
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        Text -> Ptr Int32 -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetIntegerList" Ptr Int32
result
        [Int32]
result' <- (Word64 -> Ptr Int32 -> IO [Int32]
forall a b. (Integral a, Storable b) => a -> Ptr b -> IO [b]
unpackStorableArrayWithLength Word64
length_') Ptr Int32
result
        Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        [Int32] -> IO [Int32]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Int32]
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetIntegerListMethodInfo
instance (signature ~ (T.Text -> T.Text -> m [Int32]), MonadIO m) => O.OverloadedMethod KeyFileGetIntegerListMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetIntegerList

instance O.OverloadedMethodInfo KeyFileGetIntegerListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetIntegerList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetIntegerList"
        })


#endif

-- method KeyFile::get_keys
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the number of keys returned, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) (-1) (TBasicType TUTF8))
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_keys" g_key_file_get_keys :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CString)

-- | Returns all keys for the group name /@groupName@/.  The array of
-- returned keys will be 'P.Nothing'-terminated, so /@length@/ may
-- optionally be 'P.Nothing'. In the event that the /@groupName@/ cannot
-- be found, 'P.Nothing' is returned and /@error@/ is set to
-- 'GI.GLib.Enums.KeyFileErrorGroupNotFound'.
-- 
-- /Since: 2.6/
keyFileGetKeys ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> m (([T.Text], Word64))
    -- ^ __Returns:__ a newly-allocated 'P.Nothing'-terminated array of strings.
    --     Use 'GI.GLib.Functions.strfreev' to free it. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetKeys :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> m ([Text], Word64)
keyFileGetKeys KeyFile
keyFile Text
groupName = IO ([Text], Word64) -> m ([Text], Word64)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], Word64) -> m ([Text], Word64))
-> IO ([Text], Word64) -> m ([Text], Word64)
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO ([Text], Word64) -> IO () -> IO ([Text], Word64)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CString
result <- (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString))
-> (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString -> Ptr Word64 -> Ptr (Ptr GError) -> IO (Ptr CString)
g_key_file_get_keys Ptr KeyFile
keyFile' CString
groupName' Ptr Word64
length_
        Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetKeys" 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
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        ([Text], Word64) -> IO ([Text], Word64)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text]
result', Word64
length_')
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetKeysMethodInfo
instance (signature ~ (T.Text -> m (([T.Text], Word64))), MonadIO m) => O.OverloadedMethod KeyFileGetKeysMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetKeys

instance O.OverloadedMethodInfo KeyFileGetKeysMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetKeys",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetKeys"
        })


#endif

-- method KeyFile::get_locale_for_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "locale"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a locale identifier or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_get_locale_for_key" g_key_file_get_locale_for_key :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- locale : TBasicType TUTF8
    IO CString

-- | Returns the actual locale which the result of
-- 'GI.GLib.Structs.KeyFile.keyFileGetLocaleString' or 'GI.GLib.Structs.KeyFile.keyFileGetLocaleStringList'
-- came from.
-- 
-- If calling 'GI.GLib.Structs.KeyFile.keyFileGetLocaleString' or
-- 'GI.GLib.Structs.KeyFile.keyFileGetLocaleStringList' with exactly the same /@keyFile@/,
-- /@groupName@/, /@key@/ and /@locale@/, the result of those functions will
-- have originally been tagged with the locale that is the result of
-- this function.
-- 
-- /Since: 2.56/
keyFileGetLocaleForKey ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> Maybe (T.Text)
    -- ^ /@locale@/: a locale identifier or 'P.Nothing'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ the locale from the file, or 'P.Nothing' if the key was not
    --   found or the entry in the file was was untranslated
keyFileGetLocaleForKey :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Maybe Text -> m (Maybe Text)
keyFileGetLocaleForKey KeyFile
keyFile Text
groupName Text
key Maybe Text
locale = 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
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
maybeLocale <- case Maybe Text
locale of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jLocale -> do
            CString
jLocale' <- Text -> IO CString
textToCString Text
jLocale
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLocale'
    CString
result <- Ptr KeyFile -> CString -> CString -> CString -> IO CString
g_key_file_get_locale_for_key Ptr KeyFile
keyFile' CString
groupName' CString
key' CString
maybeLocale
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLocale
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data KeyFileGetLocaleForKeyMethodInfo
instance (signature ~ (T.Text -> T.Text -> Maybe (T.Text) -> m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod KeyFileGetLocaleForKeyMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetLocaleForKey

instance O.OverloadedMethodInfo KeyFileGetLocaleForKeyMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetLocaleForKey",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetLocaleForKey"
        })


#endif

-- method KeyFile::get_locale_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "locale"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a locale identifier or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_locale_string" g_key_file_get_locale_string :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- locale : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | Returns the value associated with /@key@/ under /@groupName@/
-- translated in the given /@locale@/ if available.  If /@locale@/ is
-- 'P.Nothing' then the current locale is assumed.
-- 
-- If /@locale@/ is to be non-'P.Nothing', or if the current locale will change over
-- the lifetime of the t'GI.GLib.Structs.KeyFile.KeyFile', it must be loaded with
-- 'GI.GLib.Flags.KeyFileFlagsKeepTranslations' in order to load strings for all locales.
-- 
-- If /@key@/ cannot be found then 'P.Nothing' is returned and /@error@/ is set
-- to 'GI.GLib.Enums.KeyFileErrorKeyNotFound'. If the value associated
-- with /@key@/ cannot be interpreted or no suitable translation can
-- be found then the untranslated value is returned.
-- 
-- /Since: 2.6/
keyFileGetLocaleString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> Maybe (T.Text)
    -- ^ /@locale@/: a locale identifier or 'P.Nothing'
    -> m T.Text
    -- ^ __Returns:__ a newly allocated string or 'P.Nothing' if the specified
    --   key cannot be found. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetLocaleString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Maybe Text -> m Text
keyFileGetLocaleString KeyFile
keyFile Text
groupName Text
key Maybe Text
locale = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
maybeLocale <- case Maybe Text
locale of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jLocale -> do
            CString
jLocale' <- Text -> IO CString
textToCString Text
jLocale
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLocale'
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString -> CString -> CString -> Ptr (Ptr GError) -> IO CString
g_key_file_get_locale_string Ptr KeyFile
keyFile' CString
groupName' CString
key' CString
maybeLocale
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetLocaleString" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLocale
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLocale
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetLocaleStringMethodInfo
instance (signature ~ (T.Text -> T.Text -> Maybe (T.Text) -> m T.Text), MonadIO m) => O.OverloadedMethod KeyFileGetLocaleStringMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetLocaleString

instance O.OverloadedMethodInfo KeyFileGetLocaleStringMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetLocaleString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetLocaleString"
        })


#endif

-- method KeyFile::get_locale_string_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "locale"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a locale identifier or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the number of returned strings or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) 4 (TBasicType TUTF8))
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_locale_string_list" g_key_file_get_locale_string_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- locale : TBasicType TUTF8
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CString)

-- | Returns the values associated with /@key@/ under /@groupName@/
-- translated in the given /@locale@/ if available.  If /@locale@/ is
-- 'P.Nothing' then the current locale is assumed.
-- 
-- If /@locale@/ is to be non-'P.Nothing', or if the current locale will change over
-- the lifetime of the t'GI.GLib.Structs.KeyFile.KeyFile', it must be loaded with
-- 'GI.GLib.Flags.KeyFileFlagsKeepTranslations' in order to load strings for all locales.
-- 
-- If /@key@/ cannot be found then 'P.Nothing' is returned and /@error@/ is set
-- to 'GI.GLib.Enums.KeyFileErrorKeyNotFound'. If the values associated
-- with /@key@/ cannot be interpreted or no suitable translations
-- can be found then the untranslated values are returned. The
-- returned array is 'P.Nothing'-terminated, so /@length@/ may optionally
-- be 'P.Nothing'.
-- 
-- /Since: 2.6/
keyFileGetLocaleStringList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> Maybe (T.Text)
    -- ^ /@locale@/: a locale identifier or 'P.Nothing'
    -> m (([T.Text], Word64))
    -- ^ __Returns:__ a newly allocated 'P.Nothing'-terminated string array
    --   or 'P.Nothing' if the key isn\'t found. The string array should be freed
    --   with 'GI.GLib.Functions.strfreev'. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetLocaleStringList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Maybe Text -> m ([Text], Word64)
keyFileGetLocaleStringList KeyFile
keyFile Text
groupName Text
key Maybe Text
locale = IO ([Text], Word64) -> m ([Text], Word64)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], Word64) -> m ([Text], Word64))
-> IO ([Text], Word64) -> m ([Text], Word64)
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
maybeLocale <- case Maybe Text
locale of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jLocale -> do
            CString
jLocale' <- Text -> IO CString
textToCString Text
jLocale
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLocale'
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO ([Text], Word64) -> IO () -> IO ([Text], Word64)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CString
result <- (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString))
-> (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString
-> CString
-> CString
-> Ptr Word64
-> Ptr (Ptr GError)
-> IO (Ptr CString)
g_key_file_get_locale_string_list Ptr KeyFile
keyFile' CString
groupName' CString
key' CString
maybeLocale Ptr Word64
length_
        Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetLocaleStringList" 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
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLocale
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        ([Text], Word64) -> IO ([Text], Word64)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text]
result', Word64
length_')
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLocale
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetLocaleStringListMethodInfo
instance (signature ~ (T.Text -> T.Text -> Maybe (T.Text) -> m (([T.Text], Word64))), MonadIO m) => O.OverloadedMethod KeyFileGetLocaleStringListMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetLocaleStringList

instance O.OverloadedMethodInfo KeyFileGetLocaleStringListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetLocaleStringList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetLocaleStringList"
        })


#endif

-- method KeyFile::get_start_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_get_start_group" g_key_file_get_start_group :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    IO CString

-- | Returns the name of the start group of the file.
-- 
-- /Since: 2.6/
keyFileGetStartGroup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> m (Maybe T.Text)
    -- ^ __Returns:__ The start group of the key file.
keyFileGetStartGroup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> m (Maybe Text)
keyFileGetStartGroup KeyFile
keyFile = 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
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
result <- Ptr KeyFile -> IO CString
g_key_file_get_start_group Ptr KeyFile
keyFile'
    Maybe Text
maybeResult <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull CString
result ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \CString
result' -> do
        Text
result'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result''
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    Maybe Text -> IO (Maybe Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
maybeResult

#if defined(ENABLE_OVERLOADING)
data KeyFileGetStartGroupMethodInfo
instance (signature ~ (m (Maybe T.Text)), MonadIO m) => O.OverloadedMethod KeyFileGetStartGroupMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetStartGroup

instance O.OverloadedMethodInfo KeyFileGetStartGroupMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetStartGroup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetStartGroup"
        })


#endif

-- method KeyFile::get_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_string" g_key_file_get_string :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | Returns the string value associated with /@key@/ under /@groupName@/.
-- Unlike 'GI.GLib.Structs.KeyFile.keyFileGetValue', this function handles escape sequences
-- like \\s.
-- 
-- In the event the key cannot be found, 'P.Nothing' is returned and
-- /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorKeyNotFound'.  In the
-- event that the /@groupName@/ cannot be found, 'P.Nothing' is returned
-- and /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorGroupNotFound'.
-- 
-- /Since: 2.6/
keyFileGetString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> m T.Text
    -- ^ __Returns:__ a newly allocated string or 'P.Nothing' if the specified
    --   key cannot be found. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m Text
keyFileGetString KeyFile
keyFile Text
groupName Text
key = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO CString
g_key_file_get_string Ptr KeyFile
keyFile' CString
groupName' CString
key'
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetString" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetStringMethodInfo
instance (signature ~ (T.Text -> T.Text -> m T.Text), MonadIO m) => O.OverloadedMethod KeyFileGetStringMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetString

instance O.OverloadedMethodInfo KeyFileGetStringMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetString"
        })


#endif

-- method KeyFile::get_string_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the number of returned strings, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TCArray True (-1) 3 (TBasicType TUTF8))
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_string_list" g_key_file_get_string_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr CString)

-- | Returns the values associated with /@key@/ under /@groupName@/.
-- 
-- In the event the key cannot be found, 'P.Nothing' is returned and
-- /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorKeyNotFound'.  In the
-- event that the /@groupName@/ cannot be found, 'P.Nothing' is returned
-- and /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorGroupNotFound'.
-- 
-- /Since: 2.6/
keyFileGetStringList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> m (([T.Text], Word64))
    -- ^ __Returns:__ 
    --  a 'P.Nothing'-terminated string array or 'P.Nothing' if the specified
    --  key cannot be found. The array should be freed with 'GI.GLib.Functions.strfreev'. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetStringList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m ([Text], Word64)
keyFileGetStringList KeyFile
keyFile Text
groupName Text
key = IO ([Text], Word64) -> m ([Text], Word64)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO ([Text], Word64) -> m ([Text], Word64))
-> IO ([Text], Word64) -> m ([Text], Word64)
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO ([Text], Word64) -> IO () -> IO ([Text], Word64)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr CString
result <- (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString))
-> (Ptr (Ptr GError) -> IO (Ptr CString)) -> IO (Ptr CString)
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString
-> CString
-> Ptr Word64
-> Ptr (Ptr GError)
-> IO (Ptr CString)
g_key_file_get_string_list Ptr KeyFile
keyFile' CString
groupName' CString
key' Ptr Word64
length_
        Text -> Ptr CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetStringList" 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
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        ([Text], Word64) -> IO ([Text], Word64)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text]
result', Word64
length_')
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetStringListMethodInfo
instance (signature ~ (T.Text -> T.Text -> m (([T.Text], Word64))), MonadIO m) => O.OverloadedMethod KeyFileGetStringListMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetStringList

instance O.OverloadedMethodInfo KeyFileGetStringListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetStringList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetStringList"
        })


#endif

-- method KeyFile::get_uint64
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a non-%NULL #GKeyFile"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a non-%NULL group name"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a non-%NULL key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt64)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_uint64" g_key_file_get_uint64 :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO Word64

-- | Returns the value associated with /@key@/ under /@groupName@/ as an unsigned
-- 64-bit integer. This is similar to 'GI.GLib.Structs.KeyFile.keyFileGetInteger' but can return
-- large positive results without truncation.
-- 
-- /Since: 2.26/
keyFileGetUint64 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a non-'P.Nothing' t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a non-'P.Nothing' group name
    -> T.Text
    -- ^ /@key@/: a non-'P.Nothing' key
    -> m Word64
    -- ^ __Returns:__ the value associated with the key as an unsigned 64-bit integer,
    -- or 0 if the key was not found or could not be parsed. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetUint64 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m Word64
keyFileGetUint64 KeyFile
keyFile Text
groupName Text
key = IO Word64 -> m Word64
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word64 -> m Word64) -> IO Word64 -> m Word64
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    IO Word64 -> IO () -> IO Word64
forall a b. IO a -> IO b -> IO a
onException (do
        Word64
result <- (Ptr (Ptr GError) -> IO Word64) -> IO Word64
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO Word64) -> IO Word64)
-> (Ptr (Ptr GError) -> IO Word64) -> IO Word64
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO Word64
g_key_file_get_uint64 Ptr KeyFile
keyFile' CString
groupName' CString
key'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Word64 -> IO Word64
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word64
result
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetUint64MethodInfo
instance (signature ~ (T.Text -> T.Text -> m Word64), MonadIO m) => O.OverloadedMethod KeyFileGetUint64MethodInfo KeyFile signature where
    overloadedMethod = keyFileGetUint64

instance O.OverloadedMethodInfo KeyFileGetUint64MethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetUint64",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetUint64"
        })


#endif

-- method KeyFile::get_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_get_value" g_key_file_get_value :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | Returns the raw value associated with /@key@/ under /@groupName@/.
-- Use 'GI.GLib.Structs.KeyFile.keyFileGetString' to retrieve an unescaped UTF-8 string.
-- 
-- In the event the key cannot be found, 'P.Nothing' is returned and
-- /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorKeyNotFound'.  In the
-- event that the /@groupName@/ cannot be found, 'P.Nothing' is returned
-- and /@error@/ is set to 'GI.GLib.Enums.KeyFileErrorGroupNotFound'.
-- 
-- /Since: 2.6/
keyFileGetValue ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> m T.Text
    -- ^ __Returns:__ a newly allocated string or 'P.Nothing' if the specified
    --  key cannot be found. /(Can throw 'Data.GI.Base.GError.GError')/
keyFileGetValue :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m Text
keyFileGetValue KeyFile
keyFile Text
groupName Text
key = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    IO Text -> IO () -> IO Text
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO CString
g_key_file_get_value Ptr KeyFile
keyFile' CString
groupName' CString
key'
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileGetValue" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileGetValueMethodInfo
instance (signature ~ (T.Text -> T.Text -> m T.Text), MonadIO m) => O.OverloadedMethod KeyFileGetValueMethodInfo KeyFile signature where
    overloadedMethod = keyFileGetValue

instance O.OverloadedMethodInfo KeyFileGetValueMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileGetValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileGetValue"
        })


#endif

-- method KeyFile::has_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_has_group" g_key_file_has_group :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    IO CInt

-- | Looks whether the key file has the group /@groupName@/.
-- 
-- /Since: 2.6/
keyFileHasGroup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> m Bool
    -- ^ __Returns:__ 'P.True' if /@groupName@/ is a part of /@keyFile@/, 'P.False'
    -- otherwise.
keyFileHasGroup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> m Bool
keyFileHasGroup KeyFile
keyFile Text
groupName = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CInt
result <- Ptr KeyFile -> CString -> IO CInt
g_key_file_has_group Ptr KeyFile
keyFile' CString
groupName'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data KeyFileHasGroupMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m) => O.OverloadedMethod KeyFileHasGroupMethodInfo KeyFile signature where
    overloadedMethod = keyFileHasGroup

instance O.OverloadedMethodInfo KeyFileHasGroupMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileHasGroup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileHasGroup"
        })


#endif

-- method KeyFile::load_from_bytes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an empty #GKeyFile struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GBytes" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFileFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from #GKeyFileFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_load_from_bytes" g_key_file_load_from_bytes :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    Ptr GLib.Bytes.Bytes ->                 -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "GLib", name = "KeyFileFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Loads a key file from the data in /@bytes@/ into an empty t'GI.GLib.Structs.KeyFile.KeyFile' structure.
-- If the object cannot be created then @/error/@ is set to a t'GI.GLib.Enums.KeyFileError'.
-- 
-- /Since: 2.50/
keyFileLoadFromBytes ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: an empty t'GI.GLib.Structs.KeyFile.KeyFile' struct
    -> GLib.Bytes.Bytes
    -- ^ /@bytes@/: a t'GI.GLib.Structs.Bytes.Bytes'
    -> [GLib.Flags.KeyFileFlags]
    -- ^ /@flags@/: flags from t'GI.GLib.Flags.KeyFileFlags'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileLoadFromBytes :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Bytes -> [KeyFileFlags] -> m ()
keyFileLoadFromBytes KeyFile
keyFile Bytes
bytes [KeyFileFlags]
flags = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes
    let flags' :: CUInt
flags' = [KeyFileFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [KeyFileFlags]
flags
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> Ptr Bytes -> CUInt -> Ptr (Ptr GError) -> IO CInt
g_key_file_load_from_bytes Ptr KeyFile
keyFile' Ptr Bytes
bytes' CUInt
flags'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileLoadFromBytesMethodInfo
instance (signature ~ (GLib.Bytes.Bytes -> [GLib.Flags.KeyFileFlags] -> m ()), MonadIO m) => O.OverloadedMethod KeyFileLoadFromBytesMethodInfo KeyFile signature where
    overloadedMethod = keyFileLoadFromBytes

instance O.OverloadedMethodInfo KeyFileLoadFromBytesMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileLoadFromBytes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileLoadFromBytes"
        })


#endif

-- method KeyFile::load_from_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an empty #GKeyFile struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "data"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "key file loaded in memory"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the length of @data in bytes (or (gsize)-1 if data is nul-terminated)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFileFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from #GKeyFileFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_load_from_data" g_key_file_load_from_data :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- data : TBasicType TUTF8
    Word64 ->                               -- length : TBasicType TUInt64
    CUInt ->                                -- flags : TInterface (Name {namespace = "GLib", name = "KeyFileFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Loads a key file from memory into an empty t'GI.GLib.Structs.KeyFile.KeyFile' structure.
-- If the object cannot be created then @/error/@ is set to a t'GI.GLib.Enums.KeyFileError'.
-- 
-- /Since: 2.6/
keyFileLoadFromData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: an empty t'GI.GLib.Structs.KeyFile.KeyFile' struct
    -> T.Text
    -- ^ /@data@/: key file loaded in memory
    -> Word64
    -- ^ /@length@/: the length of /@data@/ in bytes (or (gsize)-1 if data is nul-terminated)
    -> [GLib.Flags.KeyFileFlags]
    -- ^ /@flags@/: flags from t'GI.GLib.Flags.KeyFileFlags'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileLoadFromData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Word64 -> [KeyFileFlags] -> m ()
keyFileLoadFromData KeyFile
keyFile Text
data_ Word64
length_ [KeyFileFlags]
flags = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
data_' <- Text -> IO CString
textToCString Text
data_
    let flags' :: CUInt
flags' = [KeyFileFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [KeyFileFlags]
flags
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString -> Word64 -> CUInt -> Ptr (Ptr GError) -> IO CInt
g_key_file_load_from_data Ptr KeyFile
keyFile' CString
data_' Word64
length_ CUInt
flags'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
data_'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
data_'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileLoadFromDataMethodInfo
instance (signature ~ (T.Text -> Word64 -> [GLib.Flags.KeyFileFlags] -> m ()), MonadIO m) => O.OverloadedMethod KeyFileLoadFromDataMethodInfo KeyFile signature where
    overloadedMethod = keyFileLoadFromData

instance O.OverloadedMethodInfo KeyFileLoadFromDataMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileLoadFromData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileLoadFromData"
        })


#endif

-- method KeyFile::load_from_data_dirs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an empty #GKeyFile struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a relative path to a filename to open and parse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "full_path"
--           , argType = TBasicType TFileName
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for a string containing the full path\n  of the file, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFileFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from #GKeyFileFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_load_from_data_dirs" g_key_file_load_from_data_dirs :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- file : TBasicType TFileName
    Ptr CString ->                          -- full_path : TBasicType TFileName
    CUInt ->                                -- flags : TInterface (Name {namespace = "GLib", name = "KeyFileFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | This function looks for a key file named /@file@/ in the paths
-- returned from 'GI.GLib.Functions.getUserDataDir' and 'GI.GLib.Functions.getSystemDataDirs',
-- loads the file into /@keyFile@/ and returns the file\'s full path in
-- /@fullPath@/.  If the file could not be loaded then an @/error/@ is
-- set to either a t'GI.GLib.Enums.FileError' or t'GI.GLib.Enums.KeyFileError'.
-- 
-- /Since: 2.6/
keyFileLoadFromDataDirs ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: an empty t'GI.GLib.Structs.KeyFile.KeyFile' struct
    -> [Char]
    -- ^ /@file@/: a relative path to a filename to open and parse
    -> [GLib.Flags.KeyFileFlags]
    -- ^ /@flags@/: flags from t'GI.GLib.Flags.KeyFileFlags'
    -> m ([Char])
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileLoadFromDataDirs :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> [Char] -> [KeyFileFlags] -> m [Char]
keyFileLoadFromDataDirs KeyFile
keyFile [Char]
file [KeyFileFlags]
flags = IO [Char] -> m [Char]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Char] -> m [Char]) -> IO [Char] -> m [Char]
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
file' <- [Char] -> IO CString
stringToCString [Char]
file
    Ptr CString
fullPath <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    let flags' :: CUInt
flags' = [KeyFileFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [KeyFileFlags]
flags
    IO [Char] -> IO () -> IO [Char]
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString -> Ptr CString -> CUInt -> Ptr (Ptr GError) -> IO CInt
g_key_file_load_from_data_dirs Ptr KeyFile
keyFile' CString
file' Ptr CString
fullPath CUInt
flags'
        CString
fullPath' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
fullPath
        [Char]
fullPath'' <- HasCallStack => CString -> IO [Char]
CString -> IO [Char]
cstringToString CString
fullPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fullPath'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
fullPath
        [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
fullPath''
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
fullPath
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileLoadFromDataDirsMethodInfo
instance (signature ~ ([Char] -> [GLib.Flags.KeyFileFlags] -> m ([Char])), MonadIO m) => O.OverloadedMethod KeyFileLoadFromDataDirsMethodInfo KeyFile signature where
    overloadedMethod = keyFileLoadFromDataDirs

instance O.OverloadedMethodInfo KeyFileLoadFromDataDirsMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileLoadFromDataDirs",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileLoadFromDataDirs"
        })


#endif

-- method KeyFile::load_from_dirs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an empty #GKeyFile struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a relative path to a filename to open and parse"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "search_dirs"
--           , argType = TCArray True (-1) (-1) (TBasicType TFileName)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "%NULL-terminated array of directories to search"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "full_path"
--           , argType = TBasicType TFileName
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for a string containing the full path\n  of the file, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFileFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from #GKeyFileFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_load_from_dirs" g_key_file_load_from_dirs :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- file : TBasicType TFileName
    Ptr CString ->                          -- search_dirs : TCArray True (-1) (-1) (TBasicType TFileName)
    Ptr CString ->                          -- full_path : TBasicType TFileName
    CUInt ->                                -- flags : TInterface (Name {namespace = "GLib", name = "KeyFileFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | This function looks for a key file named /@file@/ in the paths
-- specified in /@searchDirs@/, loads the file into /@keyFile@/ and
-- returns the file\'s full path in /@fullPath@/.
-- 
-- If the file could not be found in any of the /@searchDirs@/,
-- 'GI.GLib.Enums.KeyFileErrorNotFound' is returned. If
-- the file is found but the OS returns an error when opening or reading the
-- file, a @/G_FILE_ERROR/@ is returned. If there is a problem parsing the file, a
-- @/G_KEY_FILE_ERROR/@ is returned.
-- 
-- /Since: 2.14/
keyFileLoadFromDirs ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: an empty t'GI.GLib.Structs.KeyFile.KeyFile' struct
    -> [Char]
    -- ^ /@file@/: a relative path to a filename to open and parse
    -> [[Char]]
    -- ^ /@searchDirs@/: 'P.Nothing'-terminated array of directories to search
    -> [GLib.Flags.KeyFileFlags]
    -- ^ /@flags@/: flags from t'GI.GLib.Flags.KeyFileFlags'
    -> m ([Char])
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileLoadFromDirs :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> [Char] -> [[Char]] -> [KeyFileFlags] -> m [Char]
keyFileLoadFromDirs KeyFile
keyFile [Char]
file [[Char]]
searchDirs [KeyFileFlags]
flags = IO [Char] -> m [Char]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Char] -> m [Char]) -> IO [Char] -> m [Char]
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
file' <- [Char] -> IO CString
stringToCString [Char]
file
    Ptr CString
searchDirs' <- [[Char]] -> IO (Ptr CString)
packZeroTerminatedFileNameArray [[Char]]
searchDirs
    Ptr CString
fullPath <- IO (Ptr CString)
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr CString)
    let flags' :: CUInt
flags' = [KeyFileFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [KeyFileFlags]
flags
    IO [Char] -> IO () -> IO [Char]
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString
-> Ptr CString
-> Ptr CString
-> CUInt
-> Ptr (Ptr GError)
-> IO CInt
g_key_file_load_from_dirs Ptr KeyFile
keyFile' CString
file' Ptr CString
searchDirs' Ptr CString
fullPath CUInt
flags'
        CString
fullPath' <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek Ptr CString
fullPath
        [Char]
fullPath'' <- HasCallStack => CString -> IO [Char]
CString -> IO [Char]
cstringToString CString
fullPath'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fullPath'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
        (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
searchDirs'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
searchDirs'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
fullPath
        [Char] -> IO [Char]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Char]
fullPath''
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
        (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
searchDirs'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
searchDirs'
        Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
fullPath
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileLoadFromDirsMethodInfo
instance (signature ~ ([Char] -> [[Char]] -> [GLib.Flags.KeyFileFlags] -> m ([Char])), MonadIO m) => O.OverloadedMethod KeyFileLoadFromDirsMethodInfo KeyFile signature where
    overloadedMethod = keyFileLoadFromDirs

instance O.OverloadedMethodInfo KeyFileLoadFromDirsMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileLoadFromDirs",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileLoadFromDirs"
        })


#endif

-- method KeyFile::load_from_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an empty #GKeyFile struct"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the path of a filename to load, in the GLib filename encoding"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFileFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "flags from #GKeyFileFlags"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_load_from_file" g_key_file_load_from_file :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- file : TBasicType TFileName
    CUInt ->                                -- flags : TInterface (Name {namespace = "GLib", name = "KeyFileFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Loads a key file into an empty t'GI.GLib.Structs.KeyFile.KeyFile' structure.
-- 
-- If the OS returns an error when opening or reading the file, a
-- @/G_FILE_ERROR/@ is returned. If there is a problem parsing the file, a
-- @/G_KEY_FILE_ERROR/@ is returned.
-- 
-- This function will never return a 'GI.GLib.Enums.KeyFileErrorNotFound' error. If the
-- /@file@/ is not found, 'GI.GLib.Enums.FileErrorNoent' is returned.
-- 
-- /Since: 2.6/
keyFileLoadFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: an empty t'GI.GLib.Structs.KeyFile.KeyFile' struct
    -> [Char]
    -- ^ /@file@/: the path of a filename to load, in the GLib filename encoding
    -> [GLib.Flags.KeyFileFlags]
    -- ^ /@flags@/: flags from t'GI.GLib.Flags.KeyFileFlags'
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileLoadFromFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> [Char] -> [KeyFileFlags] -> m ()
keyFileLoadFromFile KeyFile
keyFile [Char]
file [KeyFileFlags]
flags = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
file' <- [Char] -> IO CString
stringToCString [Char]
file
    let flags' :: CUInt
flags' = [KeyFileFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [KeyFileFlags]
flags
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CUInt -> Ptr (Ptr GError) -> IO CInt
g_key_file_load_from_file Ptr KeyFile
keyFile' CString
file' CUInt
flags'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
file'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileLoadFromFileMethodInfo
instance (signature ~ ([Char] -> [GLib.Flags.KeyFileFlags] -> m ()), MonadIO m) => O.OverloadedMethod KeyFileLoadFromFileMethodInfo KeyFile signature where
    overloadedMethod = keyFileLoadFromFile

instance O.OverloadedMethodInfo KeyFileLoadFromFileMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileLoadFromFile",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileLoadFromFile"
        })


#endif

-- method KeyFile::remove_comment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_remove_comment" g_key_file_remove_comment :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Removes a comment above /@key@/ from /@groupName@/.
-- If /@key@/ is 'P.Nothing' then /@comment@/ will be removed above /@groupName@/.
-- If both /@key@/ and /@groupName@/ are 'P.Nothing', then /@comment@/ will
-- be removed above the first group in the file.
-- 
-- /Since: 2.6/
keyFileRemoveComment ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> Maybe (T.Text)
    -- ^ /@groupName@/: a group name, or 'P.Nothing'
    -> Maybe (T.Text)
    -- ^ /@key@/: a key
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileRemoveComment :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Maybe Text -> Maybe Text -> m ()
keyFileRemoveComment KeyFile
keyFile Maybe Text
groupName Maybe Text
key = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
maybeGroupName <- case Maybe Text
groupName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jGroupName -> do
            CString
jGroupName' <- Text -> IO CString
textToCString Text
jGroupName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGroupName'
    CString
maybeKey <- case Maybe Text
key of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jKey -> do
            CString
jKey' <- Text -> IO CString
textToCString Text
jKey
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jKey'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO CInt
g_key_file_remove_comment Ptr KeyFile
keyFile' CString
maybeGroupName CString
maybeKey
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeKey
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeKey
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileRemoveCommentMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (T.Text) -> m ()), MonadIO m) => O.OverloadedMethod KeyFileRemoveCommentMethodInfo KeyFile signature where
    overloadedMethod = keyFileRemoveComment

instance O.OverloadedMethodInfo KeyFileRemoveCommentMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileRemoveComment",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileRemoveComment"
        })


#endif

-- method KeyFile::remove_group
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_remove_group" g_key_file_remove_group :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Removes the specified group, /@groupName@/,
-- from the key file.
-- 
-- /Since: 2.6/
keyFileRemoveGroup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileRemoveGroup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> m ()
keyFileRemoveGroup KeyFile
keyFile Text
groupName = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> Ptr (Ptr GError) -> IO CInt
g_key_file_remove_group Ptr KeyFile
keyFile' CString
groupName'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileRemoveGroupMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod KeyFileRemoveGroupMethodInfo KeyFile signature where
    overloadedMethod = keyFileRemoveGroup

instance O.OverloadedMethodInfo KeyFileRemoveGroupMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileRemoveGroup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileRemoveGroup"
        })


#endif

-- method KeyFile::remove_key
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key name to remove"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_remove_key" g_key_file_remove_key :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Removes /@key@/ in /@groupName@/ from the key file.
-- 
-- /Since: 2.6/
keyFileRemoveKey ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key name to remove
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileRemoveKey :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> m ()
keyFileRemoveKey KeyFile
keyFile Text
groupName Text
key = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> CString -> Ptr (Ptr GError) -> IO CInt
g_key_file_remove_key Ptr KeyFile
keyFile' CString
groupName' CString
key'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileRemoveKeyMethodInfo
instance (signature ~ (T.Text -> T.Text -> m ()), MonadIO m) => O.OverloadedMethod KeyFileRemoveKeyMethodInfo KeyFile signature where
    overloadedMethod = keyFileRemoveKey

instance O.OverloadedMethodInfo KeyFileRemoveKeyMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileRemoveKey",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileRemoveKey"
        })


#endif

-- method KeyFile::save_to_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the name of the file to write to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_save_to_file" g_key_file_save_to_file :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- filename : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Writes the contents of /@keyFile@/ to /@filename@/ using
-- 'GI.GLib.Functions.fileSetContents'. If you need stricter guarantees about durability of
-- the written file than are provided by 'GI.GLib.Functions.fileSetContents', use
-- 'GI.GLib.Functions.fileSetContentsFull' with the return value of 'GI.GLib.Structs.KeyFile.keyFileToData'.
-- 
-- This function can fail for any of the reasons that
-- 'GI.GLib.Functions.fileSetContents' may fail.
-- 
-- /Since: 2.40/
keyFileSaveToFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@filename@/: the name of the file to write to
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileSaveToFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> m ()
keyFileSaveToFile KeyFile
keyFile Text
filename = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
filename' <- Text -> IO CString
textToCString Text
filename
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> Ptr (Ptr GError) -> IO CInt
g_key_file_save_to_file Ptr KeyFile
keyFile' CString
filename'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileSaveToFileMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSaveToFileMethodInfo KeyFile signature where
    overloadedMethod = keyFileSaveToFile

instance O.OverloadedMethodInfo KeyFileSaveToFileMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSaveToFile",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSaveToFile"
        })


#endif

-- method KeyFile::set_boolean
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "%TRUE or %FALSE" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_boolean" g_key_file_set_boolean :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()

-- | Associates a new boolean value with /@key@/ under /@groupName@/.
-- If /@key@/ cannot be found then it is created.
-- 
-- /Since: 2.6/
keyFileSetBoolean ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> Bool
    -- ^ /@value@/: 'P.True' or 'P.False'
    -> m ()
keyFileSetBoolean :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Bool -> m ()
keyFileSetBoolean KeyFile
keyFile Text
groupName Text
key Bool
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    let value' :: CInt
value' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
value
    Ptr KeyFile -> CString -> CString -> CInt -> IO ()
g_key_file_set_boolean Ptr KeyFile
keyFile' CString
groupName' CString
key' CInt
value'
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetBooleanMethodInfo
instance (signature ~ (T.Text -> T.Text -> Bool -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetBooleanMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetBoolean

instance O.OverloadedMethodInfo KeyFileSetBooleanMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetBoolean",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetBoolean"
        })


#endif

-- method KeyFile::set_boolean_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "list"
--           , argType = TCArray False (-1) 4 (TBasicType TBoolean)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of boolean values"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "length of @list" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "length of @list" , sinceVersion = Nothing }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_boolean_list" g_key_file_set_boolean_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr CInt ->                             -- list : TCArray False (-1) 4 (TBasicType TBoolean)
    Word64 ->                               -- length : TBasicType TUInt64
    IO ()

-- | Associates a list of boolean values with /@key@/ under /@groupName@/.
-- If /@key@/ cannot be found then it is created.
-- If /@groupName@/ is 'P.Nothing', the start_group is used.
-- 
-- /Since: 2.6/
keyFileSetBooleanList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> [Bool]
    -- ^ /@list@/: an array of boolean values
    -> m ()
keyFileSetBooleanList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> [Bool] -> m ()
keyFileSetBooleanList KeyFile
keyFile Text
groupName Text
key [Bool]
list = 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
    let length_ :: Word64
length_ = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [Bool] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Bool]
list
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr CInt
list' <- ((Bool -> CInt) -> [Bool] -> IO (Ptr CInt)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum)) [Bool]
list
    Ptr KeyFile -> CString -> CString -> Ptr CInt -> Word64 -> IO ()
g_key_file_set_boolean_list Ptr KeyFile
keyFile' CString
groupName' CString
key' Ptr CInt
list' Word64
length_
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Ptr CInt -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CInt
list'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetBooleanListMethodInfo
instance (signature ~ (T.Text -> T.Text -> [Bool] -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetBooleanListMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetBooleanList

instance O.OverloadedMethodInfo KeyFileSetBooleanListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetBooleanList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetBooleanList"
        })


#endif

-- method KeyFile::set_comment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "comment"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a comment" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_set_comment" g_key_file_set_comment :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- comment : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Places a comment above /@key@/ from /@groupName@/.
-- 
-- If /@key@/ is 'P.Nothing' then /@comment@/ will be written above /@groupName@/.
-- If both /@key@/ and /@groupName@/  are 'P.Nothing', then /@comment@/ will be
-- written above the first group in the file.
-- 
-- Note that this function prepends a \'#\' comment marker to
-- each line of /@comment@/.
-- 
-- /Since: 2.6/
keyFileSetComment ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> Maybe (T.Text)
    -- ^ /@groupName@/: a group name, or 'P.Nothing'
    -> Maybe (T.Text)
    -- ^ /@key@/: a key
    -> T.Text
    -- ^ /@comment@/: a comment
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
keyFileSetComment :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Maybe Text -> Maybe Text -> Text -> m ()
keyFileSetComment KeyFile
keyFile Maybe Text
groupName Maybe Text
key Text
comment = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
maybeGroupName <- case Maybe Text
groupName of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jGroupName -> do
            CString
jGroupName' <- Text -> IO CString
textToCString Text
jGroupName
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGroupName'
    CString
maybeKey <- case Maybe Text
key of
        Maybe Text
Nothing -> CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jKey -> do
            CString
jKey' <- Text -> IO CString
textToCString Text
jKey
            CString -> IO CString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jKey'
    CString
comment' <- Text -> IO CString
textToCString Text
comment
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString -> CString -> CString -> Ptr (Ptr GError) -> IO CInt
g_key_file_set_comment Ptr KeyFile
keyFile' CString
maybeGroupName CString
maybeKey CString
comment'
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeKey
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
comment'
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeKey
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
comment'
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileSetCommentMethodInfo
instance (signature ~ (Maybe (T.Text) -> Maybe (T.Text) -> T.Text -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetCommentMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetComment

instance O.OverloadedMethodInfo KeyFileSetCommentMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetComment",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetComment"
        })


#endif

-- method KeyFile::set_double
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a double value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_double" g_key_file_set_double :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CDouble ->                              -- value : TBasicType TDouble
    IO ()

-- | Associates a new double value with /@key@/ under /@groupName@/.
-- If /@key@/ cannot be found then it is created.
-- 
-- /Since: 2.12/
keyFileSetDouble ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> Double
    -- ^ /@value@/: a double value
    -> m ()
keyFileSetDouble :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Double -> m ()
keyFileSetDouble KeyFile
keyFile Text
groupName Text
key Double
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    let value' :: CDouble
value' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
value
    Ptr KeyFile -> CString -> CString -> CDouble -> IO ()
g_key_file_set_double Ptr KeyFile
keyFile' CString
groupName' CString
key' CDouble
value'
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetDoubleMethodInfo
instance (signature ~ (T.Text -> T.Text -> Double -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetDoubleMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetDouble

instance O.OverloadedMethodInfo KeyFileSetDoubleMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetDouble",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetDouble"
        })


#endif

-- method KeyFile::set_double_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "list"
--           , argType = TCArray False (-1) 4 (TBasicType TDouble)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of double values"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of double values in @list"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of double values in @list"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_double_list" g_key_file_set_double_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr CDouble ->                          -- list : TCArray False (-1) 4 (TBasicType TDouble)
    Word64 ->                               -- length : TBasicType TUInt64
    IO ()

-- | Associates a list of double values with /@key@/ under
-- /@groupName@/.  If /@key@/ cannot be found then it is created.
-- 
-- /Since: 2.12/
keyFileSetDoubleList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> [Double]
    -- ^ /@list@/: an array of double values
    -> m ()
keyFileSetDoubleList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> [Double] -> m ()
keyFileSetDoubleList KeyFile
keyFile Text
groupName Text
key [Double]
list = 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
    let length_ :: Word64
length_ = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [Double] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Double]
list
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr CDouble
list' <- ((Double -> CDouble) -> [Double] -> IO (Ptr CDouble)
forall a b. Storable b => (a -> b) -> [a] -> IO (Ptr b)
packMapStorableArray Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac) [Double]
list
    Ptr KeyFile -> CString -> CString -> Ptr CDouble -> Word64 -> IO ()
g_key_file_set_double_list Ptr KeyFile
keyFile' CString
groupName' CString
key' Ptr CDouble
list' Word64
length_
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
list'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetDoubleListMethodInfo
instance (signature ~ (T.Text -> T.Text -> [Double] -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetDoubleListMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetDoubleList

instance O.OverloadedMethodInfo KeyFileSetDoubleListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetDoubleList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetDoubleList"
        })


#endif

-- method KeyFile::set_int64
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an integer value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_int64" g_key_file_set_int64 :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Int64 ->                                -- value : TBasicType TInt64
    IO ()

-- | Associates a new integer value with /@key@/ under /@groupName@/.
-- If /@key@/ cannot be found then it is created.
-- 
-- /Since: 2.26/
keyFileSetInt64 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> Int64
    -- ^ /@value@/: an integer value
    -> m ()
keyFileSetInt64 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Int64 -> m ()
keyFileSetInt64 KeyFile
keyFile Text
groupName Text
key Int64
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr KeyFile -> CString -> CString -> Int64 -> IO ()
g_key_file_set_int64 Ptr KeyFile
keyFile' CString
groupName' CString
key' Int64
value
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetInt64MethodInfo
instance (signature ~ (T.Text -> T.Text -> Int64 -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetInt64MethodInfo KeyFile signature where
    overloadedMethod = keyFileSetInt64

instance O.OverloadedMethodInfo KeyFileSetInt64MethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetInt64",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetInt64"
        })


#endif

-- method KeyFile::set_integer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an integer value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_integer" g_key_file_set_integer :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Int32 ->                                -- value : TBasicType TInt
    IO ()

-- | Associates a new integer value with /@key@/ under /@groupName@/.
-- If /@key@/ cannot be found then it is created.
-- 
-- /Since: 2.6/
keyFileSetInteger ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> Int32
    -- ^ /@value@/: an integer value
    -> m ()
keyFileSetInteger :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Int32 -> m ()
keyFileSetInteger KeyFile
keyFile Text
groupName Text
key Int32
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr KeyFile -> CString -> CString -> Int32 -> IO ()
g_key_file_set_integer Ptr KeyFile
keyFile' CString
groupName' CString
key' Int32
value
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetIntegerMethodInfo
instance (signature ~ (T.Text -> T.Text -> Int32 -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetIntegerMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetInteger

instance O.OverloadedMethodInfo KeyFileSetIntegerMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetInteger",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetInteger"
        })


#endif

-- method KeyFile::set_integer_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "list"
--           , argType = TCArray False (-1) 4 (TBasicType TInt)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of integer values"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of integer values in @list"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "length"
--              , argType = TBasicType TUInt64
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "number of integer values in @list"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_integer_list" g_key_file_set_integer_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr Int32 ->                            -- list : TCArray False (-1) 4 (TBasicType TInt)
    Word64 ->                               -- length : TBasicType TUInt64
    IO ()

-- | Associates a list of integer values with /@key@/ under /@groupName@/.
-- If /@key@/ cannot be found then it is created.
-- 
-- /Since: 2.6/
keyFileSetIntegerList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> [Int32]
    -- ^ /@list@/: an array of integer values
    -> m ()
keyFileSetIntegerList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> [Int32] -> m ()
keyFileSetIntegerList KeyFile
keyFile Text
groupName Text
key [Int32]
list = 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
    let length_ :: Word64
length_ = Int -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word64) -> Int -> Word64
forall a b. (a -> b) -> a -> b
$ [Int32] -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
P.length [Int32]
list
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr Int32
list' <- [Int32] -> IO (Ptr Int32)
forall a. Storable a => [a] -> IO (Ptr a)
packStorableArray [Int32]
list
    Ptr KeyFile -> CString -> CString -> Ptr Int32 -> Word64 -> IO ()
g_key_file_set_integer_list Ptr KeyFile
keyFile' CString
groupName' CString
key' Ptr Int32
list' Word64
length_
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
list'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetIntegerListMethodInfo
instance (signature ~ (T.Text -> T.Text -> [Int32] -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetIntegerListMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetIntegerList

instance O.OverloadedMethodInfo KeyFileSetIntegerListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetIntegerList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetIntegerList"
        })


#endif

-- method KeyFile::set_list_separator
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "separator"
--           , argType = TBasicType TInt8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the separator" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_list_separator" g_key_file_set_list_separator :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    Int8 ->                                 -- separator : TBasicType TInt8
    IO ()

-- | Sets the character which is used to separate
-- values in lists. Typically \';\' or \',\' are used
-- as separators. The default list separator is \';\'.
-- 
-- /Since: 2.6/
keyFileSetListSeparator ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> Int8
    -- ^ /@separator@/: the separator
    -> m ()
keyFileSetListSeparator :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Int8 -> m ()
keyFileSetListSeparator KeyFile
keyFile Int8
separator = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    Ptr KeyFile -> Int8 -> IO ()
g_key_file_set_list_separator Ptr KeyFile
keyFile' Int8
separator
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetListSeparatorMethodInfo
instance (signature ~ (Int8 -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetListSeparatorMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetListSeparator

instance O.OverloadedMethodInfo KeyFileSetListSeparatorMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetListSeparator",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetListSeparator"
        })


#endif

-- method KeyFile::set_locale_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "locale"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a locale identifier"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_locale_string" g_key_file_set_locale_string :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- locale : TBasicType TUTF8
    CString ->                              -- string : TBasicType TUTF8
    IO ()

-- | Associates a string value for /@key@/ and /@locale@/ under /@groupName@/.
-- If the translation for /@key@/ cannot be found then it is created.
-- 
-- /Since: 2.6/
keyFileSetLocaleString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> T.Text
    -- ^ /@locale@/: a locale identifier
    -> T.Text
    -- ^ /@string@/: a string
    -> m ()
keyFileSetLocaleString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Text -> Text -> m ()
keyFileSetLocaleString KeyFile
keyFile Text
groupName Text
key Text
locale Text
string = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
locale' <- Text -> IO CString
textToCString Text
locale
    CString
string' <- Text -> IO CString
textToCString Text
string
    Ptr KeyFile -> CString -> CString -> CString -> CString -> IO ()
g_key_file_set_locale_string Ptr KeyFile
keyFile' CString
groupName' CString
key' CString
locale' CString
string'
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
locale'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetLocaleStringMethodInfo
instance (signature ~ (T.Text -> T.Text -> T.Text -> T.Text -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetLocaleStringMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetLocaleString

instance O.OverloadedMethodInfo KeyFileSetLocaleStringMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetLocaleString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetLocaleString"
        })


#endif

-- method KeyFile::set_locale_string_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "locale"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a locale identifier"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "list"
--           , argType = TCArray True (-1) 5 (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a %NULL-terminated array of locale string values"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the length of @list"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_locale_string_list" g_key_file_set_locale_string_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- locale : TBasicType TUTF8
    Ptr CString ->                          -- list : TCArray True (-1) 5 (TBasicType TUTF8)
    Word64 ->                               -- length : TBasicType TUInt64
    IO ()

-- | Associates a list of string values for /@key@/ and /@locale@/ under
-- /@groupName@/.  If the translation for /@key@/ cannot be found then
-- it is created.
-- 
-- /Since: 2.6/
keyFileSetLocaleStringList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> T.Text
    -- ^ /@locale@/: a locale identifier
    -> [T.Text]
    -- ^ /@list@/: a 'P.Nothing'-terminated array of locale string values
    -> Word64
    -- ^ /@length@/: the length of /@list@/
    -> m ()
keyFileSetLocaleStringList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Text -> [Text] -> Word64 -> m ()
keyFileSetLocaleStringList KeyFile
keyFile Text
groupName Text
key Text
locale [Text]
list Word64
length_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
locale' <- Text -> IO CString
textToCString Text
locale
    Ptr CString
list' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
list
    Ptr KeyFile
-> CString -> CString -> CString -> Ptr CString -> Word64 -> IO ()
g_key_file_set_locale_string_list Ptr KeyFile
keyFile' CString
groupName' CString
key' CString
locale' Ptr CString
list' Word64
length_
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
locale'
    (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
list'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
list'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetLocaleStringListMethodInfo
instance (signature ~ (T.Text -> T.Text -> T.Text -> [T.Text] -> Word64 -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetLocaleStringListMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetLocaleStringList

instance O.OverloadedMethodInfo KeyFileSetLocaleStringListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetLocaleStringList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetLocaleStringList"
        })


#endif

-- method KeyFile::set_string
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "string"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_string" g_key_file_set_string :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- string : TBasicType TUTF8
    IO ()

-- | Associates a new string value with /@key@/ under /@groupName@/.
-- If /@key@/ cannot be found then it is created.
-- If /@groupName@/ cannot be found then it is created.
-- Unlike 'GI.GLib.Structs.KeyFile.keyFileSetValue', this function handles characters
-- that need escaping, such as newlines.
-- 
-- /Since: 2.6/
keyFileSetString ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> T.Text
    -- ^ /@string@/: a string
    -> m ()
keyFileSetString :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Text -> m ()
keyFileSetString KeyFile
keyFile Text
groupName Text
key Text
string = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
string' <- Text -> IO CString
textToCString Text
string
    Ptr KeyFile -> CString -> CString -> CString -> IO ()
g_key_file_set_string Ptr KeyFile
keyFile' CString
groupName' CString
key' CString
string'
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
string'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetStringMethodInfo
instance (signature ~ (T.Text -> T.Text -> T.Text -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetStringMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetString

instance O.OverloadedMethodInfo KeyFileSetStringMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetString",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetString"
        })


#endif

-- method KeyFile::set_string_list
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "list"
--           , argType = TCArray True (-1) 4 (TBasicType TUTF8)
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of string values"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "number of string values in @list"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_string_list" g_key_file_set_string_list :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Ptr CString ->                          -- list : TCArray True (-1) 4 (TBasicType TUTF8)
    Word64 ->                               -- length : TBasicType TUInt64
    IO ()

-- | Associates a list of string values for /@key@/ under /@groupName@/.
-- If /@key@/ cannot be found then it is created.
-- If /@groupName@/ cannot be found then it is created.
-- 
-- /Since: 2.6/
keyFileSetStringList ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> [T.Text]
    -- ^ /@list@/: an array of string values
    -> Word64
    -- ^ /@length@/: number of string values in /@list@/
    -> m ()
keyFileSetStringList :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> [Text] -> Word64 -> m ()
keyFileSetStringList KeyFile
keyFile Text
groupName Text
key [Text]
list Word64
length_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr CString
list' <- [Text] -> IO (Ptr CString)
packZeroTerminatedUTF8CArray [Text]
list
    Ptr KeyFile -> CString -> CString -> Ptr CString -> Word64 -> IO ()
g_key_file_set_string_list Ptr KeyFile
keyFile' CString
groupName' CString
key' Ptr CString
list' Word64
length_
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    (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
list'
    Ptr CString -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CString
list'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetStringListMethodInfo
instance (signature ~ (T.Text -> T.Text -> [T.Text] -> Word64 -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetStringListMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetStringList

instance O.OverloadedMethodInfo KeyFileSetStringListMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetStringList",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetStringList"
        })


#endif

-- method KeyFile::set_uint64
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUInt64
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an integer value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_uint64" g_key_file_set_uint64 :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    Word64 ->                               -- value : TBasicType TUInt64
    IO ()

-- | Associates a new integer value with /@key@/ under /@groupName@/.
-- If /@key@/ cannot be found then it is created.
-- 
-- /Since: 2.26/
keyFileSetUint64 ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> Word64
    -- ^ /@value@/: an integer value
    -> m ()
keyFileSetUint64 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Word64 -> m ()
keyFileSetUint64 KeyFile
keyFile Text
groupName Text
key Word64
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr KeyFile -> CString -> CString -> Word64 -> IO ()
g_key_file_set_uint64 Ptr KeyFile
keyFile' CString
groupName' CString
key' Word64
value
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetUint64MethodInfo
instance (signature ~ (T.Text -> T.Text -> Word64 -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetUint64MethodInfo KeyFile signature where
    overloadedMethod = keyFileSetUint64

instance O.OverloadedMethodInfo KeyFileSetUint64MethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetUint64",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetUint64"
        })


#endif

-- method KeyFile::set_value
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a group name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_set_value" g_key_file_set_value :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    IO ()

-- | Associates a new value with /@key@/ under /@groupName@/.
-- 
-- If /@key@/ cannot be found then it is created. If /@groupName@/ cannot
-- be found then it is created. To set an UTF-8 string which may contain
-- characters that need escaping (such as newlines or spaces), use
-- 'GI.GLib.Structs.KeyFile.keyFileSetString'.
-- 
-- /Since: 2.6/
keyFileSetValue ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> T.Text
    -- ^ /@groupName@/: a group name
    -> T.Text
    -- ^ /@key@/: a key
    -> T.Text
    -- ^ /@value@/: a string
    -> m ()
keyFileSetValue :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Text -> Text -> Text -> m ()
keyFileSetValue KeyFile
keyFile Text
groupName Text
key Text
value = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
groupName' <- Text -> IO CString
textToCString Text
groupName
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
value' <- Text -> IO CString
textToCString Text
value
    Ptr KeyFile -> CString -> CString -> CString -> IO ()
g_key_file_set_value Ptr KeyFile
keyFile' CString
groupName' CString
key' CString
value'
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
groupName'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
value'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileSetValueMethodInfo
instance (signature ~ (T.Text -> T.Text -> T.Text -> m ()), MonadIO m) => O.OverloadedMethod KeyFileSetValueMethodInfo KeyFile signature where
    overloadedMethod = keyFileSetValue

instance O.OverloadedMethodInfo KeyFileSetValueMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileSetValue",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileSetValue"
        })


#endif

-- method KeyFile::to_data
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GKeyFile" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TUInt64
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "return location for the length of the\n  returned string, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : True
-- Skip return : False

foreign import ccall "g_key_file_to_data" g_key_file_to_data :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString

-- | This function outputs /@keyFile@/ as a string.
-- 
-- Note that this function never reports an error,
-- so it is safe to pass 'P.Nothing' as /@error@/.
-- 
-- /Since: 2.6/
keyFileToData ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> m ((T.Text, Word64))
    -- ^ __Returns:__ a newly allocated string holding
    --   the contents of the t'GI.GLib.Structs.KeyFile.KeyFile' /(Can throw 'Data.GI.Base.GError.GError')/
keyFileToData :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> m (Text, Word64)
keyFileToData KeyFile
keyFile = IO (Text, Word64) -> m (Text, Word64)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Text, Word64) -> m (Text, Word64))
-> IO (Text, Word64) -> m (Text, Word64)
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    Ptr Word64
length_ <- IO (Ptr Word64)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Word64)
    IO (Text, Word64) -> IO () -> IO (Text, Word64)
forall a b. IO a -> IO b -> IO a
onException (do
        CString
result <- (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CString) -> IO CString)
-> (Ptr (Ptr GError) -> IO CString) -> IO CString
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> Ptr Word64 -> Ptr (Ptr GError) -> IO CString
g_key_file_to_data Ptr KeyFile
keyFile' Ptr Word64
length_
        Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"keyFileToData" CString
result
        Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
result
        Word64
length_' <- Ptr Word64 -> IO Word64
forall a. Storable a => Ptr a -> IO a
peek Ptr Word64
length_
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
        (Text, Word64) -> IO (Text, Word64)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
result', Word64
length_')
     ) (do
        Ptr Word64 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Word64
length_
     )

#if defined(ENABLE_OVERLOADING)
data KeyFileToDataMethodInfo
instance (signature ~ (m ((T.Text, Word64))), MonadIO m) => O.OverloadedMethod KeyFileToDataMethodInfo KeyFile signature where
    overloadedMethod = keyFileToData

instance O.OverloadedMethodInfo KeyFileToDataMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileToData",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileToData"
        })


#endif

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

foreign import ccall "g_key_file_unref" g_key_file_unref :: 
    Ptr KeyFile ->                          -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    IO ()

-- | Decreases the reference count of /@keyFile@/ by 1. If the reference count
-- reaches zero, frees the key file and all its allocated memory.
-- 
-- /Since: 2.32/
keyFileUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    KeyFile
    -- ^ /@keyFile@/: a t'GI.GLib.Structs.KeyFile.KeyFile'
    -> m ()
keyFileUnref :: forall (m :: * -> *). (HasCallStack, MonadIO m) => KeyFile -> m ()
keyFileUnref KeyFile
keyFile = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    Ptr KeyFile -> IO ()
g_key_file_unref Ptr KeyFile
keyFile'
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data KeyFileUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod KeyFileUnrefMethodInfo KeyFile signature where
    overloadedMethod = keyFileUnref

instance O.OverloadedMethodInfo KeyFileUnrefMethodInfo KeyFile where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.GLib.Structs.KeyFile.keyFileUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-glib-2.0.29/docs/GI-GLib-Structs-KeyFile.html#v:keyFileUnref"
        })


#endif

-- method KeyFile::error_quark
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TBasicType TUInt32)
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_error_quark" g_key_file_error_quark :: 
    IO Word32

-- | /No description available in the introspection data./
keyFileErrorQuark ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m Word32
keyFileErrorQuark :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Word32
keyFileErrorQuark  = IO Word32 -> m Word32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ do
    Word32
result <- IO Word32
g_key_file_error_quark
    Word32 -> IO Word32
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveKeyFileMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveKeyFileMethod "hasGroup" o = KeyFileHasGroupMethodInfo
    ResolveKeyFileMethod "loadFromBytes" o = KeyFileLoadFromBytesMethodInfo
    ResolveKeyFileMethod "loadFromData" o = KeyFileLoadFromDataMethodInfo
    ResolveKeyFileMethod "loadFromDataDirs" o = KeyFileLoadFromDataDirsMethodInfo
    ResolveKeyFileMethod "loadFromDirs" o = KeyFileLoadFromDirsMethodInfo
    ResolveKeyFileMethod "loadFromFile" o = KeyFileLoadFromFileMethodInfo
    ResolveKeyFileMethod "removeComment" o = KeyFileRemoveCommentMethodInfo
    ResolveKeyFileMethod "removeGroup" o = KeyFileRemoveGroupMethodInfo
    ResolveKeyFileMethod "removeKey" o = KeyFileRemoveKeyMethodInfo
    ResolveKeyFileMethod "saveToFile" o = KeyFileSaveToFileMethodInfo
    ResolveKeyFileMethod "toData" o = KeyFileToDataMethodInfo
    ResolveKeyFileMethod "unref" o = KeyFileUnrefMethodInfo
    ResolveKeyFileMethod "getBoolean" o = KeyFileGetBooleanMethodInfo
    ResolveKeyFileMethod "getBooleanList" o = KeyFileGetBooleanListMethodInfo
    ResolveKeyFileMethod "getComment" o = KeyFileGetCommentMethodInfo
    ResolveKeyFileMethod "getDouble" o = KeyFileGetDoubleMethodInfo
    ResolveKeyFileMethod "getDoubleList" o = KeyFileGetDoubleListMethodInfo
    ResolveKeyFileMethod "getGroups" o = KeyFileGetGroupsMethodInfo
    ResolveKeyFileMethod "getInt64" o = KeyFileGetInt64MethodInfo
    ResolveKeyFileMethod "getInteger" o = KeyFileGetIntegerMethodInfo
    ResolveKeyFileMethod "getIntegerList" o = KeyFileGetIntegerListMethodInfo
    ResolveKeyFileMethod "getKeys" o = KeyFileGetKeysMethodInfo
    ResolveKeyFileMethod "getLocaleForKey" o = KeyFileGetLocaleForKeyMethodInfo
    ResolveKeyFileMethod "getLocaleString" o = KeyFileGetLocaleStringMethodInfo
    ResolveKeyFileMethod "getLocaleStringList" o = KeyFileGetLocaleStringListMethodInfo
    ResolveKeyFileMethod "getStartGroup" o = KeyFileGetStartGroupMethodInfo
    ResolveKeyFileMethod "getString" o = KeyFileGetStringMethodInfo
    ResolveKeyFileMethod "getStringList" o = KeyFileGetStringListMethodInfo
    ResolveKeyFileMethod "getUint64" o = KeyFileGetUint64MethodInfo
    ResolveKeyFileMethod "getValue" o = KeyFileGetValueMethodInfo
    ResolveKeyFileMethod "setBoolean" o = KeyFileSetBooleanMethodInfo
    ResolveKeyFileMethod "setBooleanList" o = KeyFileSetBooleanListMethodInfo
    ResolveKeyFileMethod "setComment" o = KeyFileSetCommentMethodInfo
    ResolveKeyFileMethod "setDouble" o = KeyFileSetDoubleMethodInfo
    ResolveKeyFileMethod "setDoubleList" o = KeyFileSetDoubleListMethodInfo
    ResolveKeyFileMethod "setInt64" o = KeyFileSetInt64MethodInfo
    ResolveKeyFileMethod "setInteger" o = KeyFileSetIntegerMethodInfo
    ResolveKeyFileMethod "setIntegerList" o = KeyFileSetIntegerListMethodInfo
    ResolveKeyFileMethod "setListSeparator" o = KeyFileSetListSeparatorMethodInfo
    ResolveKeyFileMethod "setLocaleString" o = KeyFileSetLocaleStringMethodInfo
    ResolveKeyFileMethod "setLocaleStringList" o = KeyFileSetLocaleStringListMethodInfo
    ResolveKeyFileMethod "setString" o = KeyFileSetStringMethodInfo
    ResolveKeyFileMethod "setStringList" o = KeyFileSetStringListMethodInfo
    ResolveKeyFileMethod "setUint64" o = KeyFileSetUint64MethodInfo
    ResolveKeyFileMethod "setValue" o = KeyFileSetValueMethodInfo
    ResolveKeyFileMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveKeyFileMethod t KeyFile, O.OverloadedMethod info KeyFile p) => OL.IsLabel t (KeyFile -> 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 ~ ResolveKeyFileMethod t KeyFile, O.OverloadedMethod info KeyFile p, R.HasField t KeyFile p) => R.HasField t KeyFile p where
    getField = O.overloadedMethod @info

#endif

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

#endif