{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.GLib.Structs.KeyFile
(
KeyFile(..) ,
noKeyFile ,
#if defined(ENABLE_OVERLOADING)
ResolveKeyFileMethod ,
#endif
keyFileErrorQuark ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetBooleanMethodInfo ,
#endif
keyFileGetBoolean ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetBooleanListMethodInfo ,
#endif
keyFileGetBooleanList ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetCommentMethodInfo ,
#endif
keyFileGetComment ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetDoubleMethodInfo ,
#endif
keyFileGetDouble ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetDoubleListMethodInfo ,
#endif
keyFileGetDoubleList ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetGroupsMethodInfo ,
#endif
keyFileGetGroups ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetInt64MethodInfo ,
#endif
keyFileGetInt64 ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetIntegerMethodInfo ,
#endif
keyFileGetInteger ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetIntegerListMethodInfo ,
#endif
keyFileGetIntegerList ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetKeysMethodInfo ,
#endif
keyFileGetKeys ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetLocaleForKeyMethodInfo ,
#endif
keyFileGetLocaleForKey ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetLocaleStringMethodInfo ,
#endif
keyFileGetLocaleString ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetLocaleStringListMethodInfo ,
#endif
keyFileGetLocaleStringList ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetStartGroupMethodInfo ,
#endif
keyFileGetStartGroup ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetStringMethodInfo ,
#endif
keyFileGetString ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetStringListMethodInfo ,
#endif
keyFileGetStringList ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetUint64MethodInfo ,
#endif
keyFileGetUint64 ,
#if defined(ENABLE_OVERLOADING)
KeyFileGetValueMethodInfo ,
#endif
keyFileGetValue ,
#if defined(ENABLE_OVERLOADING)
KeyFileHasGroupMethodInfo ,
#endif
keyFileHasGroup ,
#if defined(ENABLE_OVERLOADING)
KeyFileLoadFromBytesMethodInfo ,
#endif
keyFileLoadFromBytes ,
#if defined(ENABLE_OVERLOADING)
KeyFileLoadFromDataMethodInfo ,
#endif
keyFileLoadFromData ,
#if defined(ENABLE_OVERLOADING)
KeyFileLoadFromDataDirsMethodInfo ,
#endif
keyFileLoadFromDataDirs ,
#if defined(ENABLE_OVERLOADING)
KeyFileLoadFromDirsMethodInfo ,
#endif
keyFileLoadFromDirs ,
#if defined(ENABLE_OVERLOADING)
KeyFileLoadFromFileMethodInfo ,
#endif
keyFileLoadFromFile ,
keyFileNew ,
#if defined(ENABLE_OVERLOADING)
KeyFileRemoveCommentMethodInfo ,
#endif
keyFileRemoveComment ,
#if defined(ENABLE_OVERLOADING)
KeyFileRemoveGroupMethodInfo ,
#endif
keyFileRemoveGroup ,
#if defined(ENABLE_OVERLOADING)
KeyFileRemoveKeyMethodInfo ,
#endif
keyFileRemoveKey ,
#if defined(ENABLE_OVERLOADING)
KeyFileSaveToFileMethodInfo ,
#endif
keyFileSaveToFile ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetBooleanMethodInfo ,
#endif
keyFileSetBoolean ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetBooleanListMethodInfo ,
#endif
keyFileSetBooleanList ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetCommentMethodInfo ,
#endif
keyFileSetComment ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetDoubleMethodInfo ,
#endif
keyFileSetDouble ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetDoubleListMethodInfo ,
#endif
keyFileSetDoubleList ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetInt64MethodInfo ,
#endif
keyFileSetInt64 ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetIntegerMethodInfo ,
#endif
keyFileSetInteger ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetIntegerListMethodInfo ,
#endif
keyFileSetIntegerList ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetListSeparatorMethodInfo ,
#endif
keyFileSetListSeparator ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetLocaleStringMethodInfo ,
#endif
keyFileSetLocaleString ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetLocaleStringListMethodInfo ,
#endif
keyFileSetLocaleStringList ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetStringMethodInfo ,
#endif
keyFileSetString ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetStringListMethodInfo ,
#endif
keyFileSetStringList ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetUint64MethodInfo ,
#endif
keyFileSetUint64 ,
#if defined(ENABLE_OVERLOADING)
KeyFileSetValueMethodInfo ,
#endif
keyFileSetValue ,
#if defined(ENABLE_OVERLOADING)
KeyFileToDataMethodInfo ,
#endif
keyFileToData ,
#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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import {-# SOURCE #-} qualified GI.GLib.Flags as GLib.Flags
import {-# SOURCE #-} qualified GI.GLib.Structs.Bytes as GLib.Bytes
newtype KeyFile = KeyFile (ManagedPtr KeyFile)
deriving (KeyFile -> KeyFile -> Bool
(KeyFile -> KeyFile -> Bool)
-> (KeyFile -> KeyFile -> Bool) -> Eq KeyFile
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: KeyFile -> KeyFile -> Bool
$c/= :: KeyFile -> KeyFile -> Bool
== :: KeyFile -> KeyFile -> Bool
$c== :: KeyFile -> KeyFile -> Bool
Eq)
foreign import ccall "g_key_file_get_type" c_g_key_file_get_type ::
IO GType
instance BoxedObject KeyFile where
boxedType :: KeyFile -> IO GType
boxedType _ = IO GType
c_g_key_file_get_type
instance B.GValue.IsGValue KeyFile where
toGValue :: KeyFile -> IO GValue
toGValue o :: KeyFile
o = do
GType
gtype <- IO GType
c_g_key_file_get_type
KeyFile -> (Ptr KeyFile -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr KeyFile
o (GType
-> (GValue -> Ptr KeyFile -> IO ()) -> Ptr KeyFile -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr KeyFile -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO KeyFile
fromGValue gv :: GValue
gv = do
Ptr KeyFile
ptr <- GValue -> IO (Ptr KeyFile)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr KeyFile)
(ManagedPtr KeyFile -> KeyFile) -> Ptr KeyFile -> IO KeyFile
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr KeyFile -> KeyFile
KeyFile Ptr KeyFile
ptr
noKeyFile :: Maybe KeyFile
noKeyFile :: Maybe KeyFile
noKeyFile = Maybe KeyFile
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList KeyFile
type instance O.AttributeList KeyFile = KeyFileAttributeList
type KeyFileAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "g_key_file_new" g_key_file_new ::
IO (Ptr KeyFile)
keyFileNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
m KeyFile
keyFileNew :: m KeyFile
keyFileNew = IO KeyFile -> m KeyFile
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 "keyFileNew" Ptr KeyFile
result
KeyFile
result' <- ((ManagedPtr KeyFile -> KeyFile) -> Ptr KeyFile -> IO KeyFile
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr KeyFile -> KeyFile
KeyFile) Ptr KeyFile
result
KeyFile -> IO KeyFile
forall (m :: * -> *) a. Monad m => a -> m a
return KeyFile
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "g_key_file_get_boolean" g_key_file_get_boolean ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CInt
keyFileGetBoolean ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m ()
keyFileGetBoolean :: KeyFile -> Text -> Text -> m ()
keyFileGetBoolean keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileGetBooleanMethodInfo KeyFile signature where
overloadedMethod = keyFileGetBoolean
#endif
foreign import ccall "g_key_file_get_boolean_list" g_key_file_get_boolean_list ::
Ptr KeyFile ->
CString ->
CString ->
Ptr Word64 ->
Ptr (Ptr GError) ->
IO (Ptr CInt)
keyFileGetBooleanList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m [Bool]
keyFileGetBooleanList :: KeyFile -> Text -> Text -> m [Bool]
keyFileGetBooleanList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO [Bool] -> m [Bool]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Bool] -> m [Bool]) -> IO [Bool] -> m [Bool]
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 "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
/= 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 (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.MethodInfo KeyFileGetBooleanListMethodInfo KeyFile signature where
overloadedMethod = keyFileGetBooleanList
#endif
foreign import ccall "g_key_file_get_comment" ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CString
keyFileGetComment ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> Maybe (T.Text)
-> T.Text
-> m T.Text
keyFile :: KeyFile
keyFile groupName :: Maybe Text
groupName key :: Text
key = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr 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
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jGroupName :: Text
jGroupName -> do
CString
jGroupName' <- Text -> IO CString
textToCString Text
jGroupName
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGroupName'
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_comment Ptr KeyFile
keyFile' CString
maybeGroupName CString
key'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "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
key'
Text -> IO Text
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
key'
)
#if defined(ENABLE_OVERLOADING)
data KeyFileGetCommentMethodInfo
instance (signature ~ (Maybe (T.Text) -> T.Text -> m T.Text), MonadIO m) => O.MethodInfo KeyFileGetCommentMethodInfo KeyFile signature where
overloadedMethod = keyFileGetComment
#endif
foreign import ccall "g_key_file_get_double" g_key_file_get_double ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CDouble
keyFileGetDouble ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m Double
keyFileGetDouble :: KeyFile -> Text -> Text -> m Double
keyFileGetDouble keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO Double -> m Double
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 (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.MethodInfo KeyFileGetDoubleMethodInfo KeyFile signature where
overloadedMethod = keyFileGetDouble
#endif
foreign import ccall "g_key_file_get_double_list" g_key_file_get_double_list ::
Ptr KeyFile ->
CString ->
CString ->
Ptr Word64 ->
Ptr (Ptr GError) ->
IO (Ptr CDouble)
keyFileGetDoubleList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m [Double]
keyFileGetDoubleList :: KeyFile -> Text -> Text -> m [Double]
keyFileGetDoubleList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO [Double] -> m [Double]
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 "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 (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.MethodInfo KeyFileGetDoubleListMethodInfo KeyFile signature where
overloadedMethod = keyFileGetDoubleList
#endif
foreign import ccall "g_key_file_get_groups" g_key_file_get_groups ::
Ptr KeyFile ->
Ptr Word64 ->
IO (Ptr CString)
keyFileGetGroups ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> m (([T.Text], Word64))
keyFileGetGroups :: KeyFile -> m ([Text], Word64)
keyFileGetGroups keyFile :: KeyFile
keyFile = IO ([Text], Word64) -> m ([Text], Word64)
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 "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 (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.MethodInfo KeyFileGetGroupsMethodInfo KeyFile signature where
overloadedMethod = keyFileGetGroups
#endif
foreign import ccall "g_key_file_get_int64" g_key_file_get_int64 ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO Int64
keyFileGetInt64 ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m Int64
keyFileGetInt64 :: KeyFile -> Text -> Text -> m Int64
keyFileGetInt64 keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO Int64 -> m Int64
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 (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.MethodInfo KeyFileGetInt64MethodInfo KeyFile signature where
overloadedMethod = keyFileGetInt64
#endif
foreign import ccall "g_key_file_get_integer" g_key_file_get_integer ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO Int32
keyFileGetInteger ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m Int32
keyFileGetInteger :: KeyFile -> Text -> Text -> m Int32
keyFileGetInteger keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO Int32 -> m Int32
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 (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.MethodInfo KeyFileGetIntegerMethodInfo KeyFile signature where
overloadedMethod = keyFileGetInteger
#endif
foreign import ccall "g_key_file_get_integer_list" g_key_file_get_integer_list ::
Ptr KeyFile ->
CString ->
CString ->
Ptr Word64 ->
Ptr (Ptr GError) ->
IO (Ptr Int32)
keyFileGetIntegerList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m [Int32]
keyFileGetIntegerList :: KeyFile -> Text -> Text -> m [Int32]
keyFileGetIntegerList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO [Int32] -> m [Int32]
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 "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 (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.MethodInfo KeyFileGetIntegerListMethodInfo KeyFile signature where
overloadedMethod = keyFileGetIntegerList
#endif
foreign import ccall "g_key_file_get_keys" g_key_file_get_keys ::
Ptr KeyFile ->
CString ->
Ptr Word64 ->
Ptr (Ptr GError) ->
IO (Ptr CString)
keyFileGetKeys ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> m (([T.Text], Word64))
keyFileGetKeys :: KeyFile -> Text -> m ([Text], Word64)
keyFileGetKeys keyFile :: KeyFile
keyFile groupName :: Text
groupName = IO ([Text], Word64) -> m ([Text], Word64)
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 "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 (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.MethodInfo KeyFileGetKeysMethodInfo KeyFile signature where
overloadedMethod = keyFileGetKeys
#endif
foreign import ccall "g_key_file_get_locale_for_key" g_key_file_get_locale_for_key ::
Ptr KeyFile ->
CString ->
CString ->
CString ->
IO CString
keyFileGetLocaleForKey ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> Maybe (T.Text)
-> m (Maybe T.Text)
keyFileGetLocaleForKey :: KeyFile -> Text -> Text -> Maybe Text -> m (Maybe Text)
keyFileGetLocaleForKey keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key locale :: Maybe Text
locale = IO (Maybe Text) -> m (Maybe Text)
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
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jLocale :: Text
jLocale -> do
CString
jLocale' <- Text -> IO CString
textToCString Text
jLocale
CString -> IO CString
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
$ \result' :: 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 (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 (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.MethodInfo KeyFileGetLocaleForKeyMethodInfo KeyFile signature where
overloadedMethod = keyFileGetLocaleForKey
#endif
foreign import ccall "g_key_file_get_locale_string" g_key_file_get_locale_string ::
Ptr KeyFile ->
CString ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CString
keyFileGetLocaleString ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> Maybe (T.Text)
-> m T.Text
keyFileGetLocaleString :: KeyFile -> Text -> Text -> Maybe Text -> m Text
keyFileGetLocaleString keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key locale :: Maybe Text
locale = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr 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
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jLocale :: Text
jLocale -> do
CString
jLocale' <- Text -> IO CString
textToCString Text
jLocale
CString -> IO CString
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 "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 (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.MethodInfo KeyFileGetLocaleStringMethodInfo KeyFile signature where
overloadedMethod = keyFileGetLocaleString
#endif
foreign import ccall "g_key_file_get_locale_string_list" g_key_file_get_locale_string_list ::
Ptr KeyFile ->
CString ->
CString ->
CString ->
Ptr Word64 ->
Ptr (Ptr GError) ->
IO (Ptr CString)
keyFileGetLocaleStringList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> Maybe (T.Text)
-> m (([T.Text], Word64))
keyFileGetLocaleStringList :: KeyFile -> Text -> Text -> Maybe Text -> m ([Text], Word64)
keyFileGetLocaleStringList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key locale :: Maybe Text
locale = IO ([Text], Word64) -> m ([Text], Word64)
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
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jLocale :: Text
jLocale -> do
CString
jLocale' <- Text -> IO CString
textToCString Text
jLocale
CString -> IO CString
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 "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 (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.MethodInfo KeyFileGetLocaleStringListMethodInfo KeyFile signature where
overloadedMethod = keyFileGetLocaleStringList
#endif
foreign import ccall "g_key_file_get_start_group" g_key_file_get_start_group ::
Ptr KeyFile ->
IO CString
keyFileGetStartGroup ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> m T.Text
keyFileGetStartGroup :: KeyFile -> m Text
keyFileGetStartGroup keyFile :: KeyFile
keyFile = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr 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'
Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "keyFileGetStartGroup" 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
Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data KeyFileGetStartGroupMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.MethodInfo KeyFileGetStartGroupMethodInfo KeyFile signature where
overloadedMethod = keyFileGetStartGroup
#endif
foreign import ccall "g_key_file_get_string" g_key_file_get_string ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CString
keyFileGetString ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m T.Text
keyFileGetString :: KeyFile -> Text -> Text -> m Text
keyFileGetString keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 "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 (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.MethodInfo KeyFileGetStringMethodInfo KeyFile signature where
overloadedMethod = keyFileGetString
#endif
foreign import ccall "g_key_file_get_string_list" g_key_file_get_string_list ::
Ptr KeyFile ->
CString ->
CString ->
Ptr Word64 ->
Ptr (Ptr GError) ->
IO (Ptr CString)
keyFileGetStringList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m (([T.Text], Word64))
keyFileGetStringList :: KeyFile -> Text -> Text -> m ([Text], Word64)
keyFileGetStringList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO ([Text], Word64) -> m ([Text], Word64)
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 "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 (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.MethodInfo KeyFileGetStringListMethodInfo KeyFile signature where
overloadedMethod = keyFileGetStringList
#endif
foreign import ccall "g_key_file_get_uint64" g_key_file_get_uint64 ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO Word64
keyFileGetUint64 ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m Word64
keyFileGetUint64 :: KeyFile -> Text -> Text -> m Word64
keyFileGetUint64 keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO Word64 -> m Word64
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 (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.MethodInfo KeyFileGetUint64MethodInfo KeyFile signature where
overloadedMethod = keyFileGetUint64
#endif
foreign import ccall "g_key_file_get_value" g_key_file_get_value ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CString
keyFileGetValue ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m T.Text
keyFileGetValue :: KeyFile -> Text -> Text -> m Text
keyFileGetValue keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 "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 (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.MethodInfo KeyFileGetValueMethodInfo KeyFile signature where
overloadedMethod = keyFileGetValue
#endif
foreign import ccall "g_key_file_has_group" g_key_file_has_group ::
Ptr KeyFile ->
CString ->
IO CInt
keyFileHasGroup ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> m Bool
keyFileHasGroup :: KeyFile -> Text -> m Bool
keyFileHasGroup keyFile :: KeyFile
keyFile groupName :: Text
groupName = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
Ptr 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
/= 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 (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.MethodInfo KeyFileHasGroupMethodInfo KeyFile signature where
overloadedMethod = keyFileHasGroup
#endif
foreign import ccall "g_key_file_load_from_bytes" g_key_file_load_from_bytes ::
Ptr KeyFile ->
Ptr GLib.Bytes.Bytes ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
keyFileLoadFromBytes ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> GLib.Bytes.Bytes
-> [GLib.Flags.KeyFileFlags]
-> m ()
keyFileLoadFromBytes :: KeyFile -> Bytes -> [KeyFileFlags] -> m ()
keyFileLoadFromBytes keyFile :: KeyFile
keyFile bytes :: Bytes
bytes flags :: [KeyFileFlags]
flags = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()
) (do
() -> IO ()
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.MethodInfo KeyFileLoadFromBytesMethodInfo KeyFile signature where
overloadedMethod = keyFileLoadFromBytes
#endif
foreign import ccall "g_key_file_load_from_data" g_key_file_load_from_data ::
Ptr KeyFile ->
CString ->
Word64 ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
keyFileLoadFromData ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> Word64
-> [GLib.Flags.KeyFileFlags]
-> m ()
keyFileLoadFromData :: KeyFile -> Text -> Word64 -> [KeyFileFlags] -> m ()
keyFileLoadFromData keyFile :: KeyFile
keyFile data_ :: Text
data_ length_ :: Word64
length_ flags :: [KeyFileFlags]
flags = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileLoadFromDataMethodInfo KeyFile signature where
overloadedMethod = keyFileLoadFromData
#endif
foreign import ccall "g_key_file_load_from_data_dirs" g_key_file_load_from_data_dirs ::
Ptr KeyFile ->
CString ->
Ptr CString ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
keyFileLoadFromDataDirs ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> [Char]
-> [GLib.Flags.KeyFileFlags]
-> m ([Char])
keyFileLoadFromDataDirs :: KeyFile -> [Char] -> [KeyFileFlags] -> m [Char]
keyFileLoadFromDataDirs keyFile :: KeyFile
keyFile file :: [Char]
file flags :: [KeyFileFlags]
flags = IO [Char] -> m [Char]
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)
allocMem :: 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 (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.MethodInfo KeyFileLoadFromDataDirsMethodInfo KeyFile signature where
overloadedMethod = keyFileLoadFromDataDirs
#endif
foreign import ccall "g_key_file_load_from_dirs" g_key_file_load_from_dirs ::
Ptr KeyFile ->
CString ->
Ptr CString ->
Ptr CString ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
keyFileLoadFromDirs ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> [Char]
-> [[Char]]
-> [GLib.Flags.KeyFileFlags]
-> m ([Char])
keyFileLoadFromDirs :: KeyFile -> [Char] -> [[Char]] -> [KeyFileFlags] -> m [Char]
keyFileLoadFromDirs keyFile :: KeyFile
keyFile file :: [Char]
file searchDirs :: [[Char]]
searchDirs flags :: [KeyFileFlags]
flags = IO [Char] -> m [Char]
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)
allocMem :: 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 (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.MethodInfo KeyFileLoadFromDirsMethodInfo KeyFile signature where
overloadedMethod = keyFileLoadFromDirs
#endif
foreign import ccall "g_key_file_load_from_file" g_key_file_load_from_file ::
Ptr KeyFile ->
CString ->
CUInt ->
Ptr (Ptr GError) ->
IO CInt
keyFileLoadFromFile ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> [Char]
-> [GLib.Flags.KeyFileFlags]
-> m ()
keyFileLoadFromFile :: KeyFile -> [Char] -> [KeyFileFlags] -> m ()
keyFileLoadFromFile keyFile :: KeyFile
keyFile file :: [Char]
file flags :: [KeyFileFlags]
flags = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileLoadFromFileMethodInfo KeyFile signature where
overloadedMethod = keyFileLoadFromFile
#endif
foreign import ccall "g_key_file_remove_comment" ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CInt
keyFileRemoveComment ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> Maybe (T.Text)
-> Maybe (T.Text)
-> m ()
keyFile :: KeyFile
keyFile groupName :: Maybe Text
groupName key :: Maybe Text
key = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jGroupName :: Text
jGroupName -> do
CString
jGroupName' <- Text -> IO CString
textToCString Text
jGroupName
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGroupName'
CString
maybeKey <- case Maybe Text
key of
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jKey :: Text
jKey -> do
CString
jKey' <- Text -> IO CString
textToCString Text
jKey
CString -> IO CString
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 (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.MethodInfo KeyFileRemoveCommentMethodInfo KeyFile signature where
overloadedMethod = keyFileRemoveComment
#endif
foreign import ccall "g_key_file_remove_group" g_key_file_remove_group ::
Ptr KeyFile ->
CString ->
Ptr (Ptr GError) ->
IO CInt
keyFileRemoveGroup ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> m ()
keyFileRemoveGroup :: KeyFile -> Text -> m ()
keyFileRemoveGroup keyFile :: KeyFile
keyFile groupName :: Text
groupName = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileRemoveGroupMethodInfo KeyFile signature where
overloadedMethod = keyFileRemoveGroup
#endif
foreign import ccall "g_key_file_remove_key" g_key_file_remove_key ::
Ptr KeyFile ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CInt
keyFileRemoveKey ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> m ()
keyFileRemoveKey :: KeyFile -> Text -> Text -> m ()
keyFileRemoveKey keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileRemoveKeyMethodInfo KeyFile signature where
overloadedMethod = keyFileRemoveKey
#endif
foreign import ccall "g_key_file_save_to_file" g_key_file_save_to_file ::
Ptr KeyFile ->
CString ->
Ptr (Ptr GError) ->
IO CInt
keyFileSaveToFile ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> m ()
keyFileSaveToFile :: KeyFile -> Text -> m ()
keyFileSaveToFile keyFile :: KeyFile
keyFile filename :: Text
filename = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSaveToFileMethodInfo KeyFile signature where
overloadedMethod = keyFileSaveToFile
#endif
foreign import ccall "g_key_file_set_boolean" g_key_file_set_boolean ::
Ptr KeyFile ->
CString ->
CString ->
CInt ->
IO ()
keyFileSetBoolean ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> Bool
-> m ()
keyFileSetBoolean :: KeyFile -> Text -> Text -> Bool -> m ()
keyFileSetBoolean keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key value :: Bool
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
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 (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.MethodInfo KeyFileSetBooleanMethodInfo KeyFile signature where
overloadedMethod = keyFileSetBoolean
#endif
foreign import ccall "g_key_file_set_boolean_list" g_key_file_set_boolean_list ::
Ptr KeyFile ->
CString ->
CString ->
Ptr CInt ->
Word64 ->
IO ()
keyFileSetBooleanList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> [Bool]
-> m ()
keyFileSetBooleanList :: KeyFile -> Text -> Text -> [Bool] -> m ()
keyFileSetBooleanList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key list :: [Bool]
list = IO () -> m ()
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 (t :: * -> *) a. Foldable t => t a -> Int
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
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum)) [Bool]
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 (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.MethodInfo KeyFileSetBooleanListMethodInfo KeyFile signature where
overloadedMethod = keyFileSetBooleanList
#endif
foreign import ccall "g_key_file_set_comment" ::
Ptr KeyFile ->
CString ->
CString ->
CString ->
Ptr (Ptr GError) ->
IO CInt
keyFileSetComment ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> Maybe (T.Text)
-> Maybe (T.Text)
-> T.Text
-> m ()
keyFile :: KeyFile
keyFile groupName :: Maybe Text
groupName key :: Maybe Text
key comment :: Text
comment = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jGroupName :: Text
jGroupName -> do
CString
jGroupName' <- Text -> IO CString
textToCString Text
jGroupName
CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGroupName'
CString
maybeKey <- case Maybe Text
key of
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
Just jKey :: Text
jKey -> do
CString
jKey' <- Text -> IO CString
textToCString Text
jKey
CString -> IO CString
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 (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.MethodInfo KeyFileSetCommentMethodInfo KeyFile signature where
overloadedMethod = keyFileSetComment
#endif
foreign import ccall "g_key_file_set_double" g_key_file_set_double ::
Ptr KeyFile ->
CString ->
CString ->
CDouble ->
IO ()
keyFileSetDouble ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> Double
-> m ()
keyFileSetDouble :: KeyFile -> Text -> Text -> Double -> m ()
keyFileSetDouble keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key value :: Double
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSetDoubleMethodInfo KeyFile signature where
overloadedMethod = keyFileSetDouble
#endif
foreign import ccall "g_key_file_set_double_list" g_key_file_set_double_list ::
Ptr KeyFile ->
CString ->
CString ->
Ptr CDouble ->
Word64 ->
IO ()
keyFileSetDoubleList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> [Double]
-> m ()
keyFileSetDoubleList :: KeyFile -> Text -> Text -> [Double] -> m ()
keyFileSetDoubleList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key list :: [Double]
list = IO () -> m ()
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 (t :: * -> *) a. Foldable t => t a -> Int
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 (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.MethodInfo KeyFileSetDoubleListMethodInfo KeyFile signature where
overloadedMethod = keyFileSetDoubleList
#endif
foreign import ccall "g_key_file_set_int64" g_key_file_set_int64 ::
Ptr KeyFile ->
CString ->
CString ->
Int64 ->
IO ()
keyFileSetInt64 ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> Int64
-> m ()
keyFileSetInt64 :: KeyFile -> Text -> Text -> Int64 -> m ()
keyFileSetInt64 keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key value :: Int64
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSetInt64MethodInfo KeyFile signature where
overloadedMethod = keyFileSetInt64
#endif
foreign import ccall "g_key_file_set_integer" g_key_file_set_integer ::
Ptr KeyFile ->
CString ->
CString ->
Int32 ->
IO ()
keyFileSetInteger ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> Int32
-> m ()
keyFileSetInteger :: KeyFile -> Text -> Text -> Int32 -> m ()
keyFileSetInteger keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key value :: Int32
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSetIntegerMethodInfo KeyFile signature where
overloadedMethod = keyFileSetInteger
#endif
foreign import ccall "g_key_file_set_integer_list" g_key_file_set_integer_list ::
Ptr KeyFile ->
CString ->
CString ->
Ptr Int32 ->
Word64 ->
IO ()
keyFileSetIntegerList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> [Int32]
-> m ()
keyFileSetIntegerList :: KeyFile -> Text -> Text -> [Int32] -> m ()
keyFileSetIntegerList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key list :: [Int32]
list = IO () -> m ()
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 (t :: * -> *) a. Foldable t => t a -> Int
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 (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.MethodInfo KeyFileSetIntegerListMethodInfo KeyFile signature where
overloadedMethod = keyFileSetIntegerList
#endif
foreign import ccall "g_key_file_set_list_separator" g_key_file_set_list_separator ::
Ptr KeyFile ->
Int8 ->
IO ()
keyFileSetListSeparator ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> Int8
-> m ()
keyFileSetListSeparator :: KeyFile -> Int8 -> m ()
keyFileSetListSeparator keyFile :: KeyFile
keyFile separator :: Int8
separator = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data KeyFileSetListSeparatorMethodInfo
instance (signature ~ (Int8 -> m ()), MonadIO m) => O.MethodInfo KeyFileSetListSeparatorMethodInfo KeyFile signature where
overloadedMethod = keyFileSetListSeparator
#endif
foreign import ccall "g_key_file_set_locale_string" g_key_file_set_locale_string ::
Ptr KeyFile ->
CString ->
CString ->
CString ->
CString ->
IO ()
keyFileSetLocaleString ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> T.Text
-> T.Text
-> m ()
keyFileSetLocaleString :: KeyFile -> Text -> Text -> Text -> Text -> m ()
keyFileSetLocaleString keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key locale :: Text
locale string :: Text
string = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSetLocaleStringMethodInfo KeyFile signature where
overloadedMethod = keyFileSetLocaleString
#endif
foreign import ccall "g_key_file_set_locale_string_list" g_key_file_set_locale_string_list ::
Ptr KeyFile ->
CString ->
CString ->
CString ->
Ptr CString ->
Word64 ->
IO ()
keyFileSetLocaleStringList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> T.Text
-> [T.Text]
-> Word64
-> m ()
keyFileSetLocaleStringList :: KeyFile -> Text -> Text -> Text -> [Text] -> Word64 -> m ()
keyFileSetLocaleStringList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key locale :: Text
locale list :: [Text]
list length_ :: Word64
length_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSetLocaleStringListMethodInfo KeyFile signature where
overloadedMethod = keyFileSetLocaleStringList
#endif
foreign import ccall "g_key_file_set_string" g_key_file_set_string ::
Ptr KeyFile ->
CString ->
CString ->
CString ->
IO ()
keyFileSetString ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> T.Text
-> m ()
keyFileSetString :: KeyFile -> Text -> Text -> Text -> m ()
keyFileSetString keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key string :: Text
string = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSetStringMethodInfo KeyFile signature where
overloadedMethod = keyFileSetString
#endif
foreign import ccall "g_key_file_set_string_list" g_key_file_set_string_list ::
Ptr KeyFile ->
CString ->
CString ->
Ptr CString ->
Word64 ->
IO ()
keyFileSetStringList ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> [T.Text]
-> Word64
-> m ()
keyFileSetStringList :: KeyFile -> Text -> Text -> [Text] -> Word64 -> m ()
keyFileSetStringList keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key list :: [Text]
list length_ :: Word64
length_ = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSetStringListMethodInfo KeyFile signature where
overloadedMethod = keyFileSetStringList
#endif
foreign import ccall "g_key_file_set_uint64" g_key_file_set_uint64 ::
Ptr KeyFile ->
CString ->
CString ->
Word64 ->
IO ()
keyFileSetUint64 ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> Word64
-> m ()
keyFileSetUint64 :: KeyFile -> Text -> Text -> Word64 -> m ()
keyFileSetUint64 keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key value :: Word64
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSetUint64MethodInfo KeyFile signature where
overloadedMethod = keyFileSetUint64
#endif
foreign import ccall "g_key_file_set_value" g_key_file_set_value ::
Ptr KeyFile ->
CString ->
CString ->
CString ->
IO ()
keyFileSetValue ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> T.Text
-> T.Text
-> T.Text
-> m ()
keyFileSetValue :: KeyFile -> Text -> Text -> Text -> m ()
keyFileSetValue keyFile :: KeyFile
keyFile groupName :: Text
groupName key :: Text
key value :: Text
value = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (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.MethodInfo KeyFileSetValueMethodInfo KeyFile signature where
overloadedMethod = keyFileSetValue
#endif
foreign import ccall "g_key_file_to_data" g_key_file_to_data ::
Ptr KeyFile ->
Ptr Word64 ->
Ptr (Ptr GError) ->
IO CString
keyFileToData ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> m ((T.Text, Word64))
keyFileToData :: KeyFile -> m (Text, Word64)
keyFileToData keyFile :: KeyFile
keyFile = IO (Text, Word64) -> m (Text, Word64)
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 "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 (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.MethodInfo KeyFileToDataMethodInfo KeyFile signature where
overloadedMethod = keyFileToData
#endif
foreign import ccall "g_key_file_unref" g_key_file_unref ::
Ptr KeyFile ->
IO ()
keyFileUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
KeyFile
-> m ()
keyFileUnref :: KeyFile -> m ()
keyFileUnref keyFile :: KeyFile
keyFile = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data KeyFileUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo KeyFileUnrefMethodInfo KeyFile signature where
overloadedMethod = keyFileUnref
#endif
foreign import ccall "g_key_file_error_quark" g_key_file_error_quark ::
IO Word32
keyFileErrorQuark ::
(B.CallStack.HasCallStack, MonadIO m) =>
m Word32
keyFileErrorQuark :: m Word32
keyFileErrorQuark = IO Word32 -> m Word32
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 (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 :: *) :: * 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.MethodInfo 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
#endif