{- |
Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
License    : LGPL-2.1
Maintainer : Iñaki García Etxebarria (garetxe@gmail.com)
-}

module GI.GLib.Functions
    ( 

 -- * Methods
-- ** access
    access                                  ,


-- ** asciiDigitValue
    asciiDigitValue                         ,


-- ** asciiDtostr
    asciiDtostr                             ,


-- ** asciiFormatd
    asciiFormatd                            ,


-- ** asciiStrcasecmp
    asciiStrcasecmp                         ,


-- ** asciiStrdown
    asciiStrdown                            ,


-- ** asciiStrncasecmp
    asciiStrncasecmp                        ,


-- ** asciiStrtod
    asciiStrtod                             ,


-- ** asciiStrtoll
    asciiStrtoll                            ,


-- ** asciiStrtoull
    asciiStrtoull                           ,


-- ** asciiStrup
    asciiStrup                              ,


-- ** asciiTolower
    asciiTolower                            ,


-- ** asciiToupper
    asciiToupper                            ,


-- ** asciiXdigitValue
    asciiXdigitValue                        ,


-- ** assertWarning
    assertWarning                           ,


-- ** assertionMessage
    assertionMessage                        ,


-- ** assertionMessageCmpstr
    assertionMessageCmpstr                  ,


-- ** assertionMessageError
    assertionMessageError                   ,


-- ** assertionMessageExpr
    assertionMessageExpr                    ,


-- ** atexit
    atexit                                  ,


-- ** atomicIntAdd
    atomicIntAdd                            ,


-- ** atomicIntAnd
    atomicIntAnd                            ,


-- ** atomicIntCompareAndExchange
    atomicIntCompareAndExchange             ,


-- ** atomicIntDecAndTest
    atomicIntDecAndTest                     ,


-- ** atomicIntExchangeAndAdd
    atomicIntExchangeAndAdd                 ,


-- ** atomicIntGet
    atomicIntGet                            ,


-- ** atomicIntInc
    atomicIntInc                            ,


-- ** atomicIntOr
    atomicIntOr                             ,


-- ** atomicIntSet
    atomicIntSet                            ,


-- ** atomicIntXor
    atomicIntXor                            ,


-- ** atomicPointerAdd
    atomicPointerAdd                        ,


-- ** atomicPointerAnd
    atomicPointerAnd                        ,


-- ** atomicPointerCompareAndExchange
    atomicPointerCompareAndExchange         ,


-- ** atomicPointerOr
    atomicPointerOr                         ,


-- ** atomicPointerSet
    atomicPointerSet                        ,


-- ** atomicPointerXor
    atomicPointerXor                        ,


-- ** base64Decode
    base64Decode                            ,


-- ** base64DecodeInplace
    base64DecodeInplace                     ,


-- ** base64Encode
    base64Encode                            ,


-- ** basename
    basename                                ,


-- ** bitLock
    bitLock                                 ,


-- ** bitNthLsf
    bitNthLsf                               ,


-- ** bitNthMsf
    bitNthMsf                               ,


-- ** bitStorage
    bitStorage                              ,


-- ** bitTrylock
    bitTrylock                              ,


-- ** bitUnlock
    bitUnlock                               ,


-- ** bookmarkFileErrorQuark
    bookmarkFileErrorQuark                  ,


-- ** buildFilenamev
    buildFilenamev                          ,


-- ** buildPathv
    buildPathv                              ,


-- ** byteArrayFree
    byteArrayFree                           ,


-- ** byteArrayFreeToBytes
    byteArrayFreeToBytes                    ,


-- ** byteArrayNew
    byteArrayNew                            ,


-- ** byteArrayNewTake
    byteArrayNewTake                        ,


-- ** byteArrayUnref
    byteArrayUnref                          ,


-- ** chdir
    chdir                                   ,


-- ** checkVersion
    checkVersion                            ,


-- ** checksumTypeGetLength
    checksumTypeGetLength                   ,


-- ** childWatchAdd
    childWatchAdd                           ,


-- ** childWatchSourceNew
    childWatchSourceNew                     ,


-- ** clearError
    clearError                              ,


-- ** close
    close                                   ,


-- ** computeChecksumForBytes
    computeChecksumForBytes                 ,


-- ** computeChecksumForData
    computeChecksumForData                  ,


-- ** computeChecksumForString
    computeChecksumForString                ,


-- ** computeHmacForData
    computeHmacForData                      ,


-- ** computeHmacForString
    computeHmacForString                    ,


-- ** convert
    convert                                 ,


-- ** convertErrorQuark
    convertErrorQuark                       ,


-- ** convertWithFallback
    convertWithFallback                     ,


-- ** convertWithIconv
    convertWithIconv                        ,


-- ** datalistClear
    datalistClear                           ,


-- ** datalistGetFlags
    datalistGetFlags                        ,


-- ** datalistIdReplaceData
    datalistIdReplaceData                   ,


-- ** datalistIdSetDataFull
    datalistIdSetDataFull                   ,


-- ** datalistInit
    datalistInit                            ,


-- ** datalistSetFlags
    datalistSetFlags                        ,


-- ** datalistUnsetFlags
    datalistUnsetFlags                      ,


-- ** datasetDestroy
    datasetDestroy                          ,


-- ** datasetIdSetDataFull
    datasetIdSetDataFull                    ,


-- ** dateGetDaysInMonth
    dateGetDaysInMonth                      ,


-- ** dateGetMondayWeeksInYear
    dateGetMondayWeeksInYear                ,


-- ** dateGetSundayWeeksInYear
    dateGetSundayWeeksInYear                ,


-- ** dateIsLeapYear
    dateIsLeapYear                          ,


-- ** dateStrftime
    dateStrftime                            ,


-- ** dateTimeCompare
    dateTimeCompare                         ,


-- ** dateTimeEqual
    dateTimeEqual                           ,


-- ** dateTimeHash
    dateTimeHash                            ,


-- ** dateValidDay
    dateValidDay                            ,


-- ** dateValidDmy
    dateValidDmy                            ,


-- ** dateValidJulian
    dateValidJulian                         ,


-- ** dateValidMonth
    dateValidMonth                          ,


-- ** dateValidWeekday
    dateValidWeekday                        ,


-- ** dateValidYear
    dateValidYear                           ,


-- ** dcgettext
    dcgettext                               ,


-- ** dgettext
    dgettext                                ,


-- ** dirMakeTmp
    dirMakeTmp                              ,


-- ** directEqual
    directEqual                             ,


-- ** directHash
    directHash                              ,


-- ** dngettext
    dngettext                               ,


-- ** doubleEqual
    doubleEqual                             ,


-- ** doubleHash
    doubleHash                              ,


-- ** dpgettext
    dpgettext                               ,


-- ** dpgettext2
    dpgettext2                              ,


-- ** environGetenv
    environGetenv                           ,


-- ** environSetenv
    environSetenv                           ,


-- ** environUnsetenv
    environUnsetenv                         ,


-- ** fileErrorFromErrno
    fileErrorFromErrno                      ,


-- ** fileErrorQuark
    fileErrorQuark                          ,


-- ** fileGetContents
    fileGetContents                         ,


-- ** fileOpenTmp
    fileOpenTmp                             ,


-- ** fileReadLink
    fileReadLink                            ,


-- ** fileSetContents
    fileSetContents                         ,


-- ** fileTest
    fileTest                                ,


-- ** filenameDisplayBasename
    filenameDisplayBasename                 ,


-- ** filenameDisplayName
    filenameDisplayName                     ,


-- ** filenameFromUri
    filenameFromUri                         ,


-- ** filenameFromUtf8
    filenameFromUtf8                        ,


-- ** filenameToUri
    filenameToUri                           ,


-- ** filenameToUtf8
    filenameToUtf8                          ,


-- ** findProgramInPath
    findProgramInPath                       ,


-- ** formatSize
    formatSize                              ,


-- ** formatSizeForDisplay
    formatSizeForDisplay                    ,


-- ** formatSizeFull
    formatSizeFull                          ,


-- ** free
    free                                    ,


-- ** getApplicationName
    getApplicationName                      ,


-- ** getCharset
    getCharset                              ,


-- ** getCodeset
    getCodeset                              ,


-- ** getCurrentDir
    getCurrentDir                           ,


-- ** getCurrentTime
    getCurrentTime                          ,


-- ** getEnviron
    getEnviron                              ,


-- ** getFilenameCharsets
    getFilenameCharsets                     ,


-- ** getHomeDir
    getHomeDir                              ,


-- ** getHostName
    getHostName                             ,


-- ** getLanguageNames
    getLanguageNames                        ,


-- ** getLocaleVariants
    getLocaleVariants                       ,


-- ** getMonotonicTime
    getMonotonicTime                        ,


-- ** getNumProcessors
    getNumProcessors                        ,


-- ** getPrgname
    getPrgname                              ,


-- ** getRealName
    getRealName                             ,


-- ** getRealTime
    getRealTime                             ,


-- ** getSystemConfigDirs
    getSystemConfigDirs                     ,


-- ** getSystemDataDirs
    getSystemDataDirs                       ,


-- ** getTmpDir
    getTmpDir                               ,


-- ** getUserCacheDir
    getUserCacheDir                         ,


-- ** getUserConfigDir
    getUserConfigDir                        ,


-- ** getUserDataDir
    getUserDataDir                          ,


-- ** getUserName
    getUserName                             ,


-- ** getUserRuntimeDir
    getUserRuntimeDir                       ,


-- ** getUserSpecialDir
    getUserSpecialDir                       ,


-- ** getenv
    getenv                                  ,


-- ** hashTableAdd
    hashTableAdd                            ,


-- ** hashTableContains
    hashTableContains                       ,


-- ** hashTableDestroy
    hashTableDestroy                        ,


-- ** hashTableInsert
    hashTableInsert                         ,


-- ** hashTableLookupExtended
    hashTableLookupExtended                 ,


-- ** hashTableRemove
    hashTableRemove                         ,


-- ** hashTableRemoveAll
    hashTableRemoveAll                      ,


-- ** hashTableReplace
    hashTableReplace                        ,


-- ** hashTableSize
    hashTableSize                           ,


-- ** hashTableSteal
    hashTableSteal                          ,


-- ** hashTableStealAll
    hashTableStealAll                       ,


-- ** hashTableUnref
    hashTableUnref                          ,


-- ** hookDestroy
    hookDestroy                             ,


-- ** hookDestroyLink
    hookDestroyLink                         ,


-- ** hookFree
    hookFree                                ,


-- ** hookInsertBefore
    hookInsertBefore                        ,


-- ** hookPrepend
    hookPrepend                             ,


-- ** hookUnref
    hookUnref                               ,


-- ** hostnameIsAsciiEncoded
    hostnameIsAsciiEncoded                  ,


-- ** hostnameIsIpAddress
    hostnameIsIpAddress                     ,


-- ** hostnameIsNonAscii
    hostnameIsNonAscii                      ,


-- ** hostnameToAscii
    hostnameToAscii                         ,


-- ** hostnameToUnicode
    hostnameToUnicode                       ,


-- ** iconv
    iconv                                   ,


-- ** idleAdd
    idleAdd                                 ,


-- ** idleRemoveByData
    idleRemoveByData                        ,


-- ** idleSourceNew
    idleSourceNew                           ,


-- ** int64Equal
    int64Equal                              ,


-- ** int64Hash
    int64Hash                               ,


-- ** intEqual
    intEqual                                ,


-- ** intHash
    intHash                                 ,


-- ** internStaticString
    internStaticString                      ,


-- ** internString
    internString                            ,


-- ** ioAddWatch
    ioAddWatch                              ,


-- ** ioChannelErrorFromErrno
    ioChannelErrorFromErrno                 ,


-- ** ioChannelErrorQuark
    ioChannelErrorQuark                     ,


-- ** ioCreateWatch
    ioCreateWatch                           ,


-- ** keyFileErrorQuark
    keyFileErrorQuark                       ,


-- ** listenv
    listenv                                 ,


-- ** localeFromUtf8
    localeFromUtf8                          ,


-- ** localeToUtf8
    localeToUtf8                            ,


-- ** logDefaultHandler
    logDefaultHandler                       ,


-- ** logRemoveHandler
    logRemoveHandler                        ,


-- ** logSetAlwaysFatal
    logSetAlwaysFatal                       ,


-- ** logSetFatalMask
    logSetFatalMask                         ,


-- ** logSetHandler
    logSetHandler                           ,


-- ** mainContextDefault
    mainContextDefault                      ,


-- ** mainContextGetThreadDefault
    mainContextGetThreadDefault             ,


-- ** mainContextRefThreadDefault
    mainContextRefThreadDefault             ,


-- ** mainCurrentSource
    mainCurrentSource                       ,


-- ** mainDepth
    mainDepth                               ,


-- ** markupErrorQuark
    markupErrorQuark                        ,


-- ** markupEscapeText
    markupEscapeText                        ,


-- ** memIsSystemMalloc
    memIsSystemMalloc                       ,


-- ** memProfile
    memProfile                              ,


-- ** memSetVtable
    memSetVtable                            ,


-- ** mkdirWithParents
    mkdirWithParents                        ,


-- ** mkdtemp
    mkdtemp                                 ,


-- ** mkdtempFull
    mkdtempFull                             ,


-- ** mkstemp
    mkstemp                                 ,


-- ** mkstempFull
    mkstempFull                             ,


-- ** nullifyPointer
    nullifyPointer                          ,


-- ** onErrorQuery
    onErrorQuery                            ,


-- ** onErrorStackTrace
    onErrorStackTrace                       ,


-- ** onceInitEnter
    onceInitEnter                           ,


-- ** onceInitLeave
    onceInitLeave                           ,


-- ** optionErrorQuark
    optionErrorQuark                        ,


-- ** parseDebugString
    parseDebugString                        ,


-- ** pathGetBasename
    pathGetBasename                         ,


-- ** pathGetDirname
    pathGetDirname                          ,


-- ** pathIsAbsolute
    pathIsAbsolute                          ,


-- ** pathSkipRoot
    pathSkipRoot                            ,


-- ** patternMatch
    patternMatch                            ,


-- ** patternMatchSimple
    patternMatchSimple                      ,


-- ** patternMatchString
    patternMatchString                      ,


-- ** pointerBitLock
    pointerBitLock                          ,


-- ** pointerBitTrylock
    pointerBitTrylock                       ,


-- ** pointerBitUnlock
    pointerBitUnlock                        ,


-- ** poll
    poll                                    ,


-- ** propagateError
    propagateError                          ,


-- ** quarkFromStaticString
    quarkFromStaticString                   ,


-- ** quarkFromString
    quarkFromString                         ,


-- ** quarkToString
    quarkToString                           ,


-- ** quarkTryString
    quarkTryString                          ,


-- ** randomDouble
    randomDouble                            ,


-- ** randomDoubleRange
    randomDoubleRange                       ,


-- ** randomInt
    randomInt                               ,


-- ** randomIntRange
    randomIntRange                          ,


-- ** randomSetSeed
    randomSetSeed                           ,


-- ** regexCheckReplacement
    regexCheckReplacement                   ,


-- ** regexErrorQuark
    regexErrorQuark                         ,


-- ** regexEscapeNul
    regexEscapeNul                          ,


-- ** regexEscapeString
    regexEscapeString                       ,


-- ** regexMatchSimple
    regexMatchSimple                        ,


-- ** regexSplitSimple
    regexSplitSimple                        ,


-- ** reloadUserSpecialDirsCache
    reloadUserSpecialDirsCache              ,


-- ** returnIfFailWarning
    returnIfFailWarning                     ,


-- ** rmdir
    rmdir                                   ,


-- ** sequenceMove
    sequenceMove                            ,


-- ** sequenceMoveRange
    sequenceMoveRange                       ,


-- ** sequenceRemove
    sequenceRemove                          ,


-- ** sequenceRemoveRange
    sequenceRemoveRange                     ,


-- ** sequenceSet
    sequenceSet                             ,


-- ** sequenceSwap
    sequenceSwap                            ,


-- ** setApplicationName
    setApplicationName                      ,


-- ** setErrorLiteral
    setErrorLiteral                         ,


-- ** setPrgname
    setPrgname                              ,


-- ** setenv
    setenv                                  ,


-- ** shellErrorQuark
    shellErrorQuark                         ,


-- ** shellParseArgv
    shellParseArgv                          ,


-- ** shellQuote
    shellQuote                              ,


-- ** shellUnquote
    shellUnquote                            ,


-- ** sliceFree1
    sliceFree1                              ,


-- ** sliceFreeChainWithOffset
    sliceFreeChainWithOffset                ,


-- ** sliceGetConfig
    sliceGetConfig                          ,


-- ** sliceGetConfigState
    sliceGetConfigState                     ,


-- ** sliceSetConfig
    sliceSetConfig                          ,


-- ** sourceRemove
    sourceRemove                            ,


-- ** sourceRemoveByFuncsUserData
    sourceRemoveByFuncsUserData             ,


-- ** sourceRemoveByUserData
    sourceRemoveByUserData                  ,


-- ** sourceSetNameById
    sourceSetNameById                       ,


-- ** spacedPrimesClosest
    spacedPrimesClosest                     ,


-- ** spawnAsync
    spawnAsync                              ,


-- ** spawnAsyncWithPipes
    spawnAsyncWithPipes                     ,


-- ** spawnCheckExitStatus
    spawnCheckExitStatus                    ,


-- ** spawnClosePid
    spawnClosePid                           ,


-- ** spawnCommandLineAsync
    spawnCommandLineAsync                   ,


-- ** spawnCommandLineSync
    spawnCommandLineSync                    ,


-- ** spawnErrorQuark
    spawnErrorQuark                         ,


-- ** spawnExitErrorQuark
    spawnExitErrorQuark                     ,


-- ** spawnSync
    spawnSync                               ,


-- ** stpcpy
    stpcpy                                  ,


-- ** strEqual
    strEqual                                ,


-- ** strHasPrefix
    strHasPrefix                            ,


-- ** strHasSuffix
    strHasSuffix                            ,


-- ** strHash
    strHash                                 ,


-- ** strIsAscii
    strIsAscii                              ,


-- ** strMatchString
    strMatchString                          ,


-- ** strToAscii
    strToAscii                              ,


-- ** strTokenizeAndFold
    strTokenizeAndFold                      ,


-- ** strcanon
    strcanon                                ,


-- ** strcasecmp
    strcasecmp                              ,


-- ** strchomp
    strchomp                                ,


-- ** strchug
    strchug                                 ,


-- ** strcmp0
    strcmp0                                 ,


-- ** strcompress
    strcompress                             ,


-- ** strdelimit
    strdelimit                              ,


-- ** strdown
    strdown                                 ,


-- ** strdup
    strdup                                  ,


-- ** strerror
    strerror                                ,


-- ** strescape
    strescape                               ,


-- ** strfreev
    strfreev                                ,


-- ** stringNew
    stringNew                               ,


-- ** stringNewLen
    stringNewLen                            ,


-- ** stringSizedNew
    stringSizedNew                          ,


-- ** stripContext
    stripContext                            ,


-- ** strjoinv
    strjoinv                                ,


-- ** strlcat
    strlcat                                 ,


-- ** strlcpy
    strlcpy                                 ,


-- ** strncasecmp
    strncasecmp                             ,


-- ** strndup
    strndup                                 ,


-- ** strnfill
    strnfill                                ,


-- ** strreverse
    strreverse                              ,


-- ** strrstr
    strrstr                                 ,


-- ** strrstrLen
    strrstrLen                              ,


-- ** strsignal
    strsignal                               ,


-- ** strstrLen
    strstrLen                               ,


-- ** strtod
    strtod                                  ,


-- ** strup
    strup                                   ,


-- ** strvContains
    strvContains                            ,


-- ** strvGetType
    strvGetType                             ,


-- ** strvLength
    strvLength                              ,


-- ** testAddDataFunc
    testAddDataFunc                         ,


-- ** testAddFunc
    testAddFunc                             ,


-- ** testAssertExpectedMessagesInternal
    testAssertExpectedMessagesInternal      ,


-- ** testBug
    testBug                                 ,


-- ** testBugBase
    testBugBase                             ,


-- ** testExpectMessage
    testExpectMessage                       ,


-- ** testFail
    testFail                                ,


-- ** testFailed
    testFailed                              ,


-- ** testGetDir
    testGetDir                              ,


-- ** testIncomplete
    testIncomplete                          ,


-- ** testLogTypeName
    testLogTypeName                         ,


-- ** testQueueDestroy
    testQueueDestroy                        ,


-- ** testQueueFree
    testQueueFree                           ,


-- ** testRandDouble
    testRandDouble                          ,


-- ** testRandDoubleRange
    testRandDoubleRange                     ,


-- ** testRandInt
    testRandInt                             ,


-- ** testRandIntRange
    testRandIntRange                        ,


-- ** testRun
    testRun                                 ,


-- ** testRunSuite
    testRunSuite                            ,


-- ** testSetNonfatalAssertions
    testSetNonfatalAssertions               ,


-- ** testSkip
    testSkip                                ,


-- ** testSubprocess
    testSubprocess                          ,


-- ** testTimerElapsed
    testTimerElapsed                        ,


-- ** testTimerLast
    testTimerLast                           ,


-- ** testTimerStart
    testTimerStart                          ,


-- ** testTrapAssertions
    testTrapAssertions                      ,


-- ** testTrapFork
    testTrapFork                            ,


-- ** testTrapHasPassed
    testTrapHasPassed                       ,


-- ** testTrapReachedTimeout
    testTrapReachedTimeout                  ,


-- ** testTrapSubprocess
    testTrapSubprocess                      ,


-- ** threadErrorQuark
    threadErrorQuark                        ,


-- ** threadExit
    threadExit                              ,


-- ** threadPoolGetMaxIdleTime
    threadPoolGetMaxIdleTime                ,


-- ** threadPoolGetMaxUnusedThreads
    threadPoolGetMaxUnusedThreads           ,


-- ** threadPoolGetNumUnusedThreads
    threadPoolGetNumUnusedThreads           ,


-- ** threadPoolSetMaxIdleTime
    threadPoolSetMaxIdleTime                ,


-- ** threadPoolSetMaxUnusedThreads
    threadPoolSetMaxUnusedThreads           ,


-- ** threadPoolStopUnusedThreads
    threadPoolStopUnusedThreads             ,


-- ** threadSelf
    threadSelf                              ,


-- ** threadYield
    threadYield                             ,


-- ** timeValFromIso8601
    timeValFromIso8601                      ,


-- ** timeoutAdd
    timeoutAdd                              ,


-- ** timeoutAddSeconds
    timeoutAddSeconds                       ,


-- ** timeoutSourceNew
    timeoutSourceNew                        ,


-- ** timeoutSourceNewSeconds
    timeoutSourceNewSeconds                 ,


-- ** trashStackHeight
    trashStackHeight                        ,


-- ** trashStackPush
    trashStackPush                          ,


-- ** unicharBreakType
    unicharBreakType                        ,


-- ** unicharCombiningClass
    unicharCombiningClass                   ,


-- ** unicharCompose
    unicharCompose                          ,


-- ** unicharDecompose
    unicharDecompose                        ,


-- ** unicharDigitValue
    unicharDigitValue                       ,


-- ** unicharGetMirrorChar
    unicharGetMirrorChar                    ,


-- ** unicharGetScript
    unicharGetScript                        ,


-- ** unicharIsalnum
    unicharIsalnum                          ,


-- ** unicharIsalpha
    unicharIsalpha                          ,


-- ** unicharIscntrl
    unicharIscntrl                          ,


-- ** unicharIsdefined
    unicharIsdefined                        ,


-- ** unicharIsdigit
    unicharIsdigit                          ,


-- ** unicharIsgraph
    unicharIsgraph                          ,


-- ** unicharIslower
    unicharIslower                          ,


-- ** unicharIsmark
    unicharIsmark                           ,


-- ** unicharIsprint
    unicharIsprint                          ,


-- ** unicharIspunct
    unicharIspunct                          ,


-- ** unicharIsspace
    unicharIsspace                          ,


-- ** unicharIstitle
    unicharIstitle                          ,


-- ** unicharIsupper
    unicharIsupper                          ,


-- ** unicharIswide
    unicharIswide                           ,


-- ** unicharIswideCjk
    unicharIswideCjk                        ,


-- ** unicharIsxdigit
    unicharIsxdigit                         ,


-- ** unicharIszerowidth
    unicharIszerowidth                      ,


-- ** unicharToUtf8
    unicharToUtf8                           ,


-- ** unicharTolower
    unicharTolower                          ,


-- ** unicharTotitle
    unicharTotitle                          ,


-- ** unicharToupper
    unicharToupper                          ,


-- ** unicharType
    unicharType                             ,


-- ** unicharValidate
    unicharValidate                         ,


-- ** unicharXdigitValue
    unicharXdigitValue                      ,


-- ** unicodeCanonicalDecomposition
    unicodeCanonicalDecomposition           ,


-- ** unicodeCanonicalOrdering
    unicodeCanonicalOrdering                ,


-- ** unicodeScriptFromIso15924
    unicodeScriptFromIso15924               ,


-- ** unicodeScriptToIso15924
    unicodeScriptToIso15924                 ,


-- ** unixErrorQuark
    unixErrorQuark                          ,


-- ** unixFdAddFull
    unixFdAddFull                           ,


-- ** unixFdSourceNew
    unixFdSourceNew                         ,


-- ** unixOpenPipe
    unixOpenPipe                            ,


-- ** unixSetFdNonblocking
    unixSetFdNonblocking                    ,


-- ** unixSignalAdd
    unixSignalAdd                           ,


-- ** unixSignalSourceNew
    unixSignalSourceNew                     ,


-- ** unlink
    unlink                                  ,


-- ** unsetenv
    unsetenv                                ,


-- ** uriEscapeString
    uriEscapeString                         ,


-- ** uriListExtractUris
    uriListExtractUris                      ,


-- ** uriParseScheme
    uriParseScheme                          ,


-- ** uriUnescapeSegment
    uriUnescapeSegment                      ,


-- ** uriUnescapeString
    uriUnescapeString                       ,


-- ** usleep
    usleep                                  ,


-- ** utf8Casefold
    utf8Casefold                            ,


-- ** utf8Collate
    utf8Collate                             ,


-- ** utf8CollateKey
    utf8CollateKey                          ,


-- ** utf8CollateKeyForFilename
    utf8CollateKeyForFilename               ,


-- ** utf8FindNextChar
    utf8FindNextChar                        ,


-- ** utf8FindPrevChar
    utf8FindPrevChar                        ,


-- ** utf8GetChar
    utf8GetChar                             ,


-- ** utf8GetCharValidated
    utf8GetCharValidated                    ,


-- ** utf8Normalize
    utf8Normalize                           ,


-- ** utf8OffsetToPointer
    utf8OffsetToPointer                     ,


-- ** utf8PointerToOffset
    utf8PointerToOffset                     ,


-- ** utf8PrevChar
    utf8PrevChar                            ,


-- ** utf8Strchr
    utf8Strchr                              ,


-- ** utf8Strdown
    utf8Strdown                             ,


-- ** utf8Strlen
    utf8Strlen                              ,


-- ** utf8Strncpy
    utf8Strncpy                             ,


-- ** utf8Strrchr
    utf8Strrchr                             ,


-- ** utf8Strreverse
    utf8Strreverse                          ,


-- ** utf8Strup
    utf8Strup                               ,


-- ** utf8Substring
    utf8Substring                           ,


-- ** utf8Validate
    utf8Validate                            ,


-- ** variantGetGtype
    variantGetGtype                         ,


-- ** variantIsObjectPath
    variantIsObjectPath                     ,


-- ** variantIsSignature
    variantIsSignature                      ,


-- ** variantParse
    variantParse                            ,


-- ** variantParseErrorPrintContext
    variantParseErrorPrintContext           ,


-- ** variantParseErrorQuark
    variantParseErrorQuark                  ,


-- ** variantParserGetErrorQuark
    variantParserGetErrorQuark              ,


-- ** variantTypeChecked_
    variantTypeChecked_                     ,


-- ** variantTypeStringIsValid
    variantTypeStringIsValid                ,


-- ** variantTypeStringScan
    variantTypeStringScan                   ,


-- ** warnMessage
    warnMessage                             ,




    ) where

import Prelude ()
import Data.GI.Base.ShortPrelude

import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map

import GI.GLib.Types
import GI.GLib.Callbacks

-- function g_warn_message
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "warnexpr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "warnexpr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_warn_message" g_warn_message :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- file : TBasicType TUTF8
    Int32 ->                                -- line : TBasicType TInt32
    CString ->                              -- func : TBasicType TUTF8
    CString ->                              -- warnexpr : TBasicType TUTF8
    IO ()


warnMessage ::
    (MonadIO m) =>
    T.Text ->                               -- domain
    T.Text ->                               -- file
    Int32 ->                                -- line
    T.Text ->                               -- func
    T.Text ->                               -- warnexpr
    m ()
warnMessage domain file line func warnexpr = liftIO $ do
    domain' <- textToCString domain
    file' <- textToCString file
    func' <- textToCString func
    warnexpr' <- textToCString warnexpr
    g_warn_message domain' file' line func' warnexpr'
    freeMem domain'
    freeMem file'
    freeMem func'
    freeMem warnexpr'
    return ()


-- function g_variant_type_string_scan
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "limit", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "limit", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_string_scan" g_variant_type_string_scan :: 
    CString ->                              -- string : TBasicType TUTF8
    CString ->                              -- limit : TBasicType TUTF8
    Ptr CString ->                          -- endptr : TBasicType TUTF8
    IO CInt


variantTypeStringScan ::
    (MonadIO m) =>
    T.Text ->                               -- string
    Maybe (T.Text) ->                       -- limit
    m (Bool,T.Text)
variantTypeStringScan string limit = liftIO $ do
    string' <- textToCString string
    maybeLimit <- case limit of
        Nothing -> return nullPtr
        Just jLimit -> do
            jLimit' <- textToCString jLimit
            return jLimit'
    endptr <- allocMem :: IO (Ptr CString)
    result <- g_variant_type_string_scan string' maybeLimit endptr
    let result' = (/= 0) result
    endptr' <- peek endptr
    endptr'' <- cstringToText endptr'
    freeMem endptr'
    freeMem string'
    freeMem maybeLimit
    freeMem endptr
    return (result', endptr'')


-- function g_variant_type_string_is_valid
-- Args : [Arg {argName = "type_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "type_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_string_is_valid" g_variant_type_string_is_valid :: 
    CString ->                              -- type_string : TBasicType TUTF8
    IO CInt


variantTypeStringIsValid ::
    (MonadIO m) =>
    T.Text ->                               -- type_string
    m Bool
variantTypeStringIsValid type_string = liftIO $ do
    type_string' <- textToCString type_string
    result <- g_variant_type_string_is_valid type_string'
    let result' = (/= 0) result
    freeMem type_string'
    return result'


-- function g_variant_type_checked_
-- Args : [Arg {argName = "arg0", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "arg0", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "VariantType"
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_type_checked_" g_variant_type_checked_ :: 
    CString ->                              -- arg0 : TBasicType TUTF8
    IO (Ptr VariantType)


variantTypeChecked_ ::
    (MonadIO m) =>
    T.Text ->                               -- arg0
    m VariantType
variantTypeChecked_ arg0 = liftIO $ do
    arg0' <- textToCString arg0
    result <- g_variant_type_checked_ arg0'
    checkUnexpectedReturnNULL "g_variant_type_checked_" result
    result' <- (newBoxed VariantType) result
    freeMem arg0'
    return result'


-- function g_variant_parser_get_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_parser_get_error_quark" g_variant_parser_get_error_quark :: 
    IO Word32

{-# DEPRECATED variantParserGetErrorQuark ["Use g_variant_parse_error_quark() instead."]#-}
variantParserGetErrorQuark ::
    (MonadIO m) =>
    m Word32
variantParserGetErrorQuark  = liftIO $ do
    result <- g_variant_parser_get_error_quark
    return result


-- function g_variant_parse_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_parse_error_quark" g_variant_parse_error_quark :: 
    IO Word32


variantParseErrorQuark ::
    (MonadIO m) =>
    m Word32
variantParseErrorQuark  = liftIO $ do
    result <- g_variant_parse_error_quark
    return result


-- function g_variant_parse_error_print_context
-- Args : [Arg {argName = "error", argType = TError, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "source_str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "error", argType = TError, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "source_str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_parse_error_print_context" g_variant_parse_error_print_context :: 
    Ptr GError ->                           -- error : TError
    CString ->                              -- source_str : TBasicType TUTF8
    IO CString


variantParseErrorPrintContext ::
    (MonadIO m) =>
    GError ->                               -- error
    T.Text ->                               -- source_str
    m T.Text
variantParseErrorPrintContext error_ source_str = liftIO $ do
    let error_' = unsafeManagedPtrGetPtr error_
    source_str' <- textToCString source_str
    result <- g_variant_parse_error_print_context error_' source_str'
    checkUnexpectedReturnNULL "g_variant_parse_error_print_context" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr error_
    freeMem source_str'
    return result'


-- function g_variant_parse
-- Args : [Arg {argName = "type", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "limit", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "type", argType = TInterface "GLib" "VariantType", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "limit", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TVariant
-- throws : True
-- Skip return : False

foreign import ccall "g_variant_parse" g_variant_parse :: 
    Ptr VariantType ->                      -- type : TInterface "GLib" "VariantType"
    CString ->                              -- text : TBasicType TUTF8
    CString ->                              -- limit : TBasicType TUTF8
    CString ->                              -- endptr : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr GVariant)


variantParse ::
    (MonadIO m) =>
    Maybe (VariantType) ->                  -- type
    T.Text ->                               -- text
    Maybe (T.Text) ->                       -- limit
    Maybe (T.Text) ->                       -- endptr
    m GVariant
variantParse type_ text limit endptr = liftIO $ do
    maybeType_ <- case type_ of
        Nothing -> return nullPtr
        Just jType_ -> do
            let jType_' = unsafeManagedPtrGetPtr jType_
            return jType_'
    text' <- textToCString text
    maybeLimit <- case limit of
        Nothing -> return nullPtr
        Just jLimit -> do
            jLimit' <- textToCString jLimit
            return jLimit'
    maybeEndptr <- case endptr of
        Nothing -> return nullPtr
        Just jEndptr -> do
            jEndptr' <- textToCString jEndptr
            return jEndptr'
    onException (do
        result <- propagateGError $ g_variant_parse maybeType_ text' maybeLimit maybeEndptr
        checkUnexpectedReturnNULL "g_variant_parse" result
        result' <- wrapGVariantPtr result
        whenJust type_ touchManagedPtr
        freeMem text'
        freeMem maybeLimit
        freeMem maybeEndptr
        return result'
     ) (do
        freeMem text'
        freeMem maybeLimit
        freeMem maybeEndptr
     )


-- function g_variant_is_signature
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_is_signature" g_variant_is_signature :: 
    CString ->                              -- string : TBasicType TUTF8
    IO CInt


variantIsSignature ::
    (MonadIO m) =>
    T.Text ->                               -- string
    m Bool
variantIsSignature string = liftIO $ do
    string' <- textToCString string
    result <- g_variant_is_signature string'
    let result' = (/= 0) result
    freeMem string'
    return result'


-- function g_variant_is_object_path
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_is_object_path" g_variant_is_object_path :: 
    CString ->                              -- string : TBasicType TUTF8
    IO CInt


variantIsObjectPath ::
    (MonadIO m) =>
    T.Text ->                               -- string
    m Bool
variantIsObjectPath string = liftIO $ do
    string' <- textToCString string
    result <- g_variant_is_object_path string'
    let result' = (/= 0) result
    freeMem string'
    return result'


-- function g_variant_get_gtype
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TGType
-- throws : False
-- Skip return : False

foreign import ccall "g_variant_get_gtype" g_variant_get_gtype :: 
    IO CGType


variantGetGtype ::
    (MonadIO m) =>
    m GType
variantGetGtype  = liftIO $ do
    result <- g_variant_get_gtype
    let result' = GType result
    return result'


-- function g_utf8_validate
-- Args : [Arg {argName = "str", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "max_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "str", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_validate" g_utf8_validate :: 
    Ptr Word8 ->                            -- str : TCArray False (-1) 1 (TBasicType TUInt8)
    Int64 ->                                -- max_len : TBasicType TInt64
    Ptr CString ->                          -- end : TBasicType TUTF8
    IO CInt


utf8Validate ::
    (MonadIO m) =>
    ByteString ->                           -- str
    m (Bool,T.Text)
utf8Validate str = liftIO $ do
    let max_len = fromIntegral $ B.length str
    str' <- packByteString str
    end <- allocMem :: IO (Ptr CString)
    result <- g_utf8_validate str' max_len end
    let result' = (/= 0) result
    end' <- peek end
    end'' <- cstringToText end'
    freeMem str'
    freeMem end
    return (result', end'')


-- function g_utf8_substring
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start_pos", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end_pos", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start_pos", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end_pos", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_substring" g_utf8_substring :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- start_pos : TBasicType TInt64
    Int64 ->                                -- end_pos : TBasicType TInt64
    IO CString


utf8Substring ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- start_pos
    Int64 ->                                -- end_pos
    m T.Text
utf8Substring str start_pos end_pos = liftIO $ do
    str' <- textToCString str
    result <- g_utf8_substring str' start_pos end_pos
    checkUnexpectedReturnNULL "g_utf8_substring" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_utf8_strup
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_strup" g_utf8_strup :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO CString


utf8Strup ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    m T.Text
utf8Strup str len = liftIO $ do
    str' <- textToCString str
    result <- g_utf8_strup str' len
    checkUnexpectedReturnNULL "g_utf8_strup" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_utf8_strreverse
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_strreverse" g_utf8_strreverse :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO CString


utf8Strreverse ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    m T.Text
utf8Strreverse str len = liftIO $ do
    str' <- textToCString str
    result <- g_utf8_strreverse str' len
    checkUnexpectedReturnNULL "g_utf8_strreverse" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_utf8_strrchr
-- Args : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_strrchr" g_utf8_strrchr :: 
    CString ->                              -- p : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    CInt ->                                 -- c : TBasicType TUniChar
    IO CString


utf8Strrchr ::
    (MonadIO m) =>
    T.Text ->                               -- p
    Int64 ->                                -- len
    Char ->                                 -- c
    m T.Text
utf8Strrchr p len c = liftIO $ do
    p' <- textToCString p
    let c' = (fromIntegral . ord) c
    result <- g_utf8_strrchr p' len c'
    checkUnexpectedReturnNULL "g_utf8_strrchr" result
    result' <- cstringToText result
    freeMem result
    freeMem p'
    return result'


-- function g_utf8_strncpy
-- Args : [Arg {argName = "dest", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dest", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_strncpy" g_utf8_strncpy :: 
    CString ->                              -- dest : TBasicType TUTF8
    CString ->                              -- src : TBasicType TUTF8
    Word64 ->                               -- n : TBasicType TUInt64
    IO CString


utf8Strncpy ::
    (MonadIO m) =>
    T.Text ->                               -- dest
    T.Text ->                               -- src
    Word64 ->                               -- n
    m T.Text
utf8Strncpy dest src n = liftIO $ do
    dest' <- textToCString dest
    src' <- textToCString src
    result <- g_utf8_strncpy dest' src' n
    checkUnexpectedReturnNULL "g_utf8_strncpy" result
    result' <- cstringToText result
    freeMem result
    freeMem dest'
    freeMem src'
    return result'


-- function g_utf8_strlen
-- Args : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_strlen" g_utf8_strlen :: 
    CString ->                              -- p : TBasicType TUTF8
    Int64 ->                                -- max : TBasicType TInt64
    IO Int64


utf8Strlen ::
    (MonadIO m) =>
    T.Text ->                               -- p
    Int64 ->                                -- max
    m Int64
utf8Strlen p max = liftIO $ do
    p' <- textToCString p
    result <- g_utf8_strlen p' max
    freeMem p'
    return result


-- function g_utf8_strdown
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_strdown" g_utf8_strdown :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO CString


utf8Strdown ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    m T.Text
utf8Strdown str len = liftIO $ do
    str' <- textToCString str
    result <- g_utf8_strdown str' len
    checkUnexpectedReturnNULL "g_utf8_strdown" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_utf8_strchr
-- Args : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_strchr" g_utf8_strchr :: 
    CString ->                              -- p : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    CInt ->                                 -- c : TBasicType TUniChar
    IO CString


utf8Strchr ::
    (MonadIO m) =>
    T.Text ->                               -- p
    Int64 ->                                -- len
    Char ->                                 -- c
    m T.Text
utf8Strchr p len c = liftIO $ do
    p' <- textToCString p
    let c' = (fromIntegral . ord) c
    result <- g_utf8_strchr p' len c'
    checkUnexpectedReturnNULL "g_utf8_strchr" result
    result' <- cstringToText result
    freeMem result
    freeMem p'
    return result'


-- function g_utf8_prev_char
-- Args : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_prev_char" g_utf8_prev_char :: 
    CString ->                              -- p : TBasicType TUTF8
    IO CString


utf8PrevChar ::
    (MonadIO m) =>
    T.Text ->                               -- p
    m T.Text
utf8PrevChar p = liftIO $ do
    p' <- textToCString p
    result <- g_utf8_prev_char p'
    checkUnexpectedReturnNULL "g_utf8_prev_char" result
    result' <- cstringToText result
    freeMem result
    freeMem p'
    return result'


-- function g_utf8_pointer_to_offset
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pos", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pos", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_pointer_to_offset" g_utf8_pointer_to_offset :: 
    CString ->                              -- str : TBasicType TUTF8
    CString ->                              -- pos : TBasicType TUTF8
    IO Int64


utf8PointerToOffset ::
    (MonadIO m) =>
    T.Text ->                               -- str
    T.Text ->                               -- pos
    m Int64
utf8PointerToOffset str pos = liftIO $ do
    str' <- textToCString str
    pos' <- textToCString pos
    result <- g_utf8_pointer_to_offset str' pos'
    freeMem str'
    freeMem pos'
    return result


-- function g_utf8_offset_to_pointer
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "offset", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "offset", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_offset_to_pointer" g_utf8_offset_to_pointer :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- offset : TBasicType TInt64
    IO CString


utf8OffsetToPointer ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- offset
    m T.Text
utf8OffsetToPointer str offset = liftIO $ do
    str' <- textToCString str
    result <- g_utf8_offset_to_pointer str' offset
    checkUnexpectedReturnNULL "g_utf8_offset_to_pointer" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_utf8_normalize
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TInterface "GLib" "NormalizeMode", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TInterface "GLib" "NormalizeMode", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_normalize" g_utf8_normalize :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    CUInt ->                                -- mode : TInterface "GLib" "NormalizeMode"
    IO CString


utf8Normalize ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    NormalizeMode ->                        -- mode
    m T.Text
utf8Normalize str len mode = liftIO $ do
    str' <- textToCString str
    let mode' = (fromIntegral . fromEnum) mode
    result <- g_utf8_normalize str' len mode'
    checkUnexpectedReturnNULL "g_utf8_normalize" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_utf8_get_char_validated
-- Args : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "max_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUniChar
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_get_char_validated" g_utf8_get_char_validated :: 
    CString ->                              -- p : TBasicType TUTF8
    Int64 ->                                -- max_len : TBasicType TInt64
    IO CInt


utf8GetCharValidated ::
    (MonadIO m) =>
    T.Text ->                               -- p
    Int64 ->                                -- max_len
    m Char
utf8GetCharValidated p max_len = liftIO $ do
    p' <- textToCString p
    result <- g_utf8_get_char_validated p' max_len
    let result' = (chr . fromIntegral) result
    freeMem p'
    return result'


-- function g_utf8_get_char
-- Args : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUniChar
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_get_char" g_utf8_get_char :: 
    CString ->                              -- p : TBasicType TUTF8
    IO CInt


utf8GetChar ::
    (MonadIO m) =>
    T.Text ->                               -- p
    m Char
utf8GetChar p = liftIO $ do
    p' <- textToCString p
    result <- g_utf8_get_char p'
    let result' = (chr . fromIntegral) result
    freeMem p'
    return result'


-- function g_utf8_find_prev_char
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_find_prev_char" g_utf8_find_prev_char :: 
    CString ->                              -- str : TBasicType TUTF8
    CString ->                              -- p : TBasicType TUTF8
    IO CString


utf8FindPrevChar ::
    (MonadIO m) =>
    T.Text ->                               -- str
    T.Text ->                               -- p
    m T.Text
utf8FindPrevChar str p = liftIO $ do
    str' <- textToCString str
    p' <- textToCString p
    result <- g_utf8_find_prev_char str' p'
    checkUnexpectedReturnNULL "g_utf8_find_prev_char" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    freeMem p'
    return result'


-- function g_utf8_find_next_char
-- Args : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "p", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_find_next_char" g_utf8_find_next_char :: 
    CString ->                              -- p : TBasicType TUTF8
    CString ->                              -- end : TBasicType TUTF8
    IO CString


utf8FindNextChar ::
    (MonadIO m) =>
    T.Text ->                               -- p
    T.Text ->                               -- end
    m T.Text
utf8FindNextChar p end = liftIO $ do
    p' <- textToCString p
    end' <- textToCString end
    result <- g_utf8_find_next_char p' end'
    checkUnexpectedReturnNULL "g_utf8_find_next_char" result
    result' <- cstringToText result
    freeMem result
    freeMem p'
    freeMem end'
    return result'


-- function g_utf8_collate_key_for_filename
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_collate_key_for_filename" g_utf8_collate_key_for_filename :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO CString


utf8CollateKeyForFilename ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    m T.Text
utf8CollateKeyForFilename str len = liftIO $ do
    str' <- textToCString str
    result <- g_utf8_collate_key_for_filename str' len
    checkUnexpectedReturnNULL "g_utf8_collate_key_for_filename" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_utf8_collate_key
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_collate_key" g_utf8_collate_key :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO CString


utf8CollateKey ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    m T.Text
utf8CollateKey str len = liftIO $ do
    str' <- textToCString str
    result <- g_utf8_collate_key str' len
    checkUnexpectedReturnNULL "g_utf8_collate_key" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_utf8_collate
-- Args : [Arg {argName = "str1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_collate" g_utf8_collate :: 
    CString ->                              -- str1 : TBasicType TUTF8
    CString ->                              -- str2 : TBasicType TUTF8
    IO Int32


utf8Collate ::
    (MonadIO m) =>
    T.Text ->                               -- str1
    T.Text ->                               -- str2
    m Int32
utf8Collate str1 str2 = liftIO $ do
    str1' <- textToCString str1
    str2' <- textToCString str2
    result <- g_utf8_collate str1' str2'
    freeMem str1'
    freeMem str2'
    return result


-- function g_utf8_casefold
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_utf8_casefold" g_utf8_casefold :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO CString


utf8Casefold ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    m T.Text
utf8Casefold str len = liftIO $ do
    str' <- textToCString str
    result <- g_utf8_casefold str' len
    checkUnexpectedReturnNULL "g_utf8_casefold" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_usleep
-- Args : [Arg {argName = "microseconds", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "microseconds", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_usleep" g_usleep :: 
    Word64 ->                               -- microseconds : TBasicType TUInt64
    IO ()


usleep ::
    (MonadIO m) =>
    Word64 ->                               -- microseconds
    m ()
usleep microseconds = liftIO $ do
    g_usleep microseconds
    return ()


-- function g_uri_unescape_string
-- Args : [Arg {argName = "escaped_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "illegal_characters", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "escaped_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "illegal_characters", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_uri_unescape_string" g_uri_unescape_string :: 
    CString ->                              -- escaped_string : TBasicType TUTF8
    CString ->                              -- illegal_characters : TBasicType TUTF8
    IO CString


uriUnescapeString ::
    (MonadIO m) =>
    T.Text ->                               -- escaped_string
    Maybe (T.Text) ->                       -- illegal_characters
    m T.Text
uriUnescapeString escaped_string illegal_characters = liftIO $ do
    escaped_string' <- textToCString escaped_string
    maybeIllegal_characters <- case illegal_characters of
        Nothing -> return nullPtr
        Just jIllegal_characters -> do
            jIllegal_characters' <- textToCString jIllegal_characters
            return jIllegal_characters'
    result <- g_uri_unescape_string escaped_string' maybeIllegal_characters
    checkUnexpectedReturnNULL "g_uri_unescape_string" result
    result' <- cstringToText result
    freeMem result
    freeMem escaped_string'
    freeMem maybeIllegal_characters
    return result'


-- function g_uri_unescape_segment
-- Args : [Arg {argName = "escaped_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "escaped_string_end", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "illegal_characters", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "escaped_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "escaped_string_end", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "illegal_characters", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_uri_unescape_segment" g_uri_unescape_segment :: 
    CString ->                              -- escaped_string : TBasicType TUTF8
    CString ->                              -- escaped_string_end : TBasicType TUTF8
    CString ->                              -- illegal_characters : TBasicType TUTF8
    IO CString


uriUnescapeSegment ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- escaped_string
    Maybe (T.Text) ->                       -- escaped_string_end
    Maybe (T.Text) ->                       -- illegal_characters
    m T.Text
uriUnescapeSegment escaped_string escaped_string_end illegal_characters = liftIO $ do
    maybeEscaped_string <- case escaped_string of
        Nothing -> return nullPtr
        Just jEscaped_string -> do
            jEscaped_string' <- textToCString jEscaped_string
            return jEscaped_string'
    maybeEscaped_string_end <- case escaped_string_end of
        Nothing -> return nullPtr
        Just jEscaped_string_end -> do
            jEscaped_string_end' <- textToCString jEscaped_string_end
            return jEscaped_string_end'
    maybeIllegal_characters <- case illegal_characters of
        Nothing -> return nullPtr
        Just jIllegal_characters -> do
            jIllegal_characters' <- textToCString jIllegal_characters
            return jIllegal_characters'
    result <- g_uri_unescape_segment maybeEscaped_string maybeEscaped_string_end maybeIllegal_characters
    checkUnexpectedReturnNULL "g_uri_unescape_segment" result
    result' <- cstringToText result
    freeMem result
    freeMem maybeEscaped_string
    freeMem maybeEscaped_string_end
    freeMem maybeIllegal_characters
    return result'


-- function g_uri_parse_scheme
-- Args : [Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_uri_parse_scheme" g_uri_parse_scheme :: 
    CString ->                              -- uri : TBasicType TUTF8
    IO CString


uriParseScheme ::
    (MonadIO m) =>
    T.Text ->                               -- uri
    m T.Text
uriParseScheme uri = liftIO $ do
    uri' <- textToCString uri
    result <- g_uri_parse_scheme uri'
    checkUnexpectedReturnNULL "g_uri_parse_scheme" result
    result' <- cstringToText result
    freeMem result
    freeMem uri'
    return result'


-- function g_uri_list_extract_uris
-- Args : [Arg {argName = "uri_list", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "uri_list", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_uri_list_extract_uris" g_uri_list_extract_uris :: 
    CString ->                              -- uri_list : TBasicType TUTF8
    IO (Ptr CString)


uriListExtractUris ::
    (MonadIO m) =>
    T.Text ->                               -- uri_list
    m [T.Text]
uriListExtractUris uri_list = liftIO $ do
    uri_list' <- textToCString uri_list
    result <- g_uri_list_extract_uris uri_list'
    checkUnexpectedReturnNULL "g_uri_list_extract_uris" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    freeMem uri_list'
    return result'


-- function g_uri_escape_string
-- Args : [Arg {argName = "unescaped", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "reserved_chars_allowed", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "allow_utf8", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "unescaped", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "reserved_chars_allowed", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "allow_utf8", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_uri_escape_string" g_uri_escape_string :: 
    CString ->                              -- unescaped : TBasicType TUTF8
    CString ->                              -- reserved_chars_allowed : TBasicType TUTF8
    CInt ->                                 -- allow_utf8 : TBasicType TBoolean
    IO CString


uriEscapeString ::
    (MonadIO m) =>
    T.Text ->                               -- unescaped
    Maybe (T.Text) ->                       -- reserved_chars_allowed
    Bool ->                                 -- allow_utf8
    m T.Text
uriEscapeString unescaped reserved_chars_allowed allow_utf8 = liftIO $ do
    unescaped' <- textToCString unescaped
    maybeReserved_chars_allowed <- case reserved_chars_allowed of
        Nothing -> return nullPtr
        Just jReserved_chars_allowed -> do
            jReserved_chars_allowed' <- textToCString jReserved_chars_allowed
            return jReserved_chars_allowed'
    let allow_utf8' = (fromIntegral . fromEnum) allow_utf8
    result <- g_uri_escape_string unescaped' maybeReserved_chars_allowed allow_utf8'
    checkUnexpectedReturnNULL "g_uri_escape_string" result
    result' <- cstringToText result
    freeMem result
    freeMem unescaped'
    freeMem maybeReserved_chars_allowed
    return result'


-- function g_unsetenv
-- Args : [Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_unsetenv" g_unsetenv :: 
    CString ->                              -- variable : TBasicType TUTF8
    IO ()


unsetenv ::
    (MonadIO m) =>
    T.Text ->                               -- variable
    m ()
unsetenv variable = liftIO $ do
    variable' <- textToCString variable
    g_unsetenv variable'
    freeMem variable'
    return ()


-- function g_unlink
-- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_unlink" g_unlink :: 
    CString ->                              -- filename : TBasicType TUTF8
    IO Int32


unlink ::
    (MonadIO m) =>
    T.Text ->                               -- filename
    m Int32
unlink filename = liftIO $ do
    filename' <- textToCString filename
    result <- g_unlink filename'
    freeMem filename'
    return result


-- function g_unix_signal_source_new
-- Args : [Arg {argName = "signum", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "signum", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "Source"
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_signal_source_new" g_unix_signal_source_new :: 
    Int32 ->                                -- signum : TBasicType TInt32
    IO (Ptr Source)


unixSignalSourceNew ::
    (MonadIO m) =>
    Int32 ->                                -- signum
    m Source
unixSignalSourceNew signum = liftIO $ do
    result <- g_unix_signal_source_new signum
    checkUnexpectedReturnNULL "g_unix_signal_source_new" result
    result' <- (wrapBoxed Source) result
    return result'


-- function g_unix_signal_add_full
-- Args : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "signum", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "handler", argType = TInterface "GLib" "SourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "notify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "signum", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "handler", argType = TInterface "GLib" "SourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_signal_add_full" g_unix_signal_add_full :: 
    Int32 ->                                -- priority : TBasicType TInt32
    Int32 ->                                -- signum : TBasicType TInt32
    FunPtr SourceFuncC ->                   -- handler : TInterface "GLib" "SourceFunc"
    Ptr () ->                               -- user_data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- notify : TInterface "GLib" "DestroyNotify"
    IO Word32


unixSignalAdd ::
    (MonadIO m) =>
    Int32 ->                                -- priority
    Int32 ->                                -- signum
    SourceFunc ->                           -- handler
    m Word32
unixSignalAdd priority signum handler = liftIO $ do
    handler' <- mkSourceFunc (sourceFuncWrapper Nothing handler)
    let user_data = castFunPtrToPtr handler'
    let notify = safeFreeFunPtrPtr
    result <- g_unix_signal_add_full priority signum handler' user_data notify
    return result


-- function g_unix_set_fd_nonblocking
-- Args : [Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nonblock", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nonblock", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_unix_set_fd_nonblocking" g_unix_set_fd_nonblocking :: 
    Int32 ->                                -- fd : TBasicType TInt32
    CInt ->                                 -- nonblock : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO CInt


unixSetFdNonblocking ::
    (MonadIO m) =>
    Int32 ->                                -- fd
    Bool ->                                 -- nonblock
    m ()
unixSetFdNonblocking fd nonblock = liftIO $ do
    let nonblock' = (fromIntegral . fromEnum) nonblock
    onException (do
        _ <- propagateGError $ g_unix_set_fd_nonblocking fd nonblock'
        return ()
     ) (do
        return ()
     )


-- function g_unix_open_pipe
-- Args : [Arg {argName = "fds", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "fds", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_unix_open_pipe" g_unix_open_pipe :: 
    Int32 ->                                -- fds : TBasicType TInt32
    Int32 ->                                -- flags : TBasicType TInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt


unixOpenPipe ::
    (MonadIO m) =>
    Int32 ->                                -- fds
    Int32 ->                                -- flags
    m ()
unixOpenPipe fds flags = liftIO $ do
    onException (do
        _ <- propagateGError $ g_unix_open_pipe fds flags
        return ()
     ) (do
        return ()
     )


-- function g_unix_fd_source_new
-- Args : [Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "condition", argType = TInterface "GLib" "IOCondition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "condition", argType = TInterface "GLib" "IOCondition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "Source"
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_fd_source_new" g_unix_fd_source_new :: 
    Int32 ->                                -- fd : TBasicType TInt32
    CUInt ->                                -- condition : TInterface "GLib" "IOCondition"
    IO (Ptr Source)


unixFdSourceNew ::
    (MonadIO m) =>
    Int32 ->                                -- fd
    [IOCondition] ->                        -- condition
    m Source
unixFdSourceNew fd condition = liftIO $ do
    let condition' = gflagsToWord condition
    result <- g_unix_fd_source_new fd condition'
    checkUnexpectedReturnNULL "g_unix_fd_source_new" result
    result' <- (wrapBoxed Source) result
    return result'


-- function g_unix_fd_add_full
-- Args : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "condition", argType = TInterface "GLib" "IOCondition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "UnixFDSourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 4, argDestroy = 5, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "notify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "condition", argType = TInterface "GLib" "IOCondition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "UnixFDSourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 4, argDestroy = 5, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_fd_add_full" g_unix_fd_add_full :: 
    Int32 ->                                -- priority : TBasicType TInt32
    Int32 ->                                -- fd : TBasicType TInt32
    CUInt ->                                -- condition : TInterface "GLib" "IOCondition"
    FunPtr UnixFDSourceFuncC ->             -- function : TInterface "GLib" "UnixFDSourceFunc"
    Ptr () ->                               -- user_data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- notify : TInterface "GLib" "DestroyNotify"
    IO Word32


unixFdAddFull ::
    (MonadIO m) =>
    Int32 ->                                -- priority
    Int32 ->                                -- fd
    [IOCondition] ->                        -- condition
    UnixFDSourceFunc ->                     -- function
    m Word32
unixFdAddFull priority fd condition function = liftIO $ do
    let condition' = gflagsToWord condition
    function' <- mkUnixFDSourceFunc (unixFDSourceFuncWrapper Nothing function)
    let user_data = castFunPtrToPtr function'
    let notify = safeFreeFunPtrPtr
    result <- g_unix_fd_add_full priority fd condition' function' user_data notify
    return result


-- function g_unix_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_unix_error_quark" g_unix_error_quark :: 
    IO Word32


unixErrorQuark ::
    (MonadIO m) =>
    m Word32
unixErrorQuark  = liftIO $ do
    result <- g_unix_error_quark
    return result


-- function g_unicode_script_to_iso15924
-- Args : [Arg {argName = "script", argType = TInterface "GLib" "UnicodeScript", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "script", argType = TInterface "GLib" "UnicodeScript", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_unicode_script_to_iso15924" g_unicode_script_to_iso15924 :: 
    CUInt ->                                -- script : TInterface "GLib" "UnicodeScript"
    IO Word32


unicodeScriptToIso15924 ::
    (MonadIO m) =>
    UnicodeScript ->                        -- script
    m Word32
unicodeScriptToIso15924 script = liftIO $ do
    let script' = (fromIntegral . fromEnum) script
    result <- g_unicode_script_to_iso15924 script'
    return result


-- function g_unicode_script_from_iso15924
-- Args : [Arg {argName = "iso15924", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "iso15924", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "UnicodeScript"
-- throws : False
-- Skip return : False

foreign import ccall "g_unicode_script_from_iso15924" g_unicode_script_from_iso15924 :: 
    Word32 ->                               -- iso15924 : TBasicType TUInt32
    IO CUInt


unicodeScriptFromIso15924 ::
    (MonadIO m) =>
    Word32 ->                               -- iso15924
    m UnicodeScript
unicodeScriptFromIso15924 iso15924 = liftIO $ do
    result <- g_unicode_script_from_iso15924 iso15924
    let result' = (toEnum . fromIntegral) result
    return result'


-- function g_unicode_canonical_ordering
-- Args : [Arg {argName = "string", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_unicode_canonical_ordering" g_unicode_canonical_ordering :: 
    CInt ->                                 -- string : TBasicType TUniChar
    Word64 ->                               -- len : TBasicType TUInt64
    IO ()


unicodeCanonicalOrdering ::
    (MonadIO m) =>
    Char ->                                 -- string
    Word64 ->                               -- len
    m ()
unicodeCanonicalOrdering string len = liftIO $ do
    let string' = (fromIntegral . ord) string
    g_unicode_canonical_ordering string' len
    return ()


-- function g_unicode_canonical_decomposition
-- Args : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result_len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result_len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUniChar
-- throws : False
-- Skip return : False

foreign import ccall "g_unicode_canonical_decomposition" g_unicode_canonical_decomposition :: 
    CInt ->                                 -- ch : TBasicType TUniChar
    Word64 ->                               -- result_len : TBasicType TUInt64
    IO CInt

{-# DEPRECATED unicodeCanonicalDecomposition ["(Since version 2.30)","Use the more flexible g_unichar_fully_decompose()","  instead."]#-}
unicodeCanonicalDecomposition ::
    (MonadIO m) =>
    Char ->                                 -- ch
    Word64 ->                               -- result_len
    m Char
unicodeCanonicalDecomposition ch result_len = liftIO $ do
    let ch' = (fromIntegral . ord) ch
    result <- g_unicode_canonical_decomposition ch' result_len
    let result' = (chr . fromIntegral) result
    return result'


-- function g_unichar_xdigit_value
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_xdigit_value" g_unichar_xdigit_value :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO Int32


unicharXdigitValue ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Int32
unicharXdigitValue c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_xdigit_value c'
    return result


-- function g_unichar_validate
-- Args : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_validate" g_unichar_validate :: 
    CInt ->                                 -- ch : TBasicType TUniChar
    IO CInt


unicharValidate ::
    (MonadIO m) =>
    Char ->                                 -- ch
    m Bool
unicharValidate ch = liftIO $ do
    let ch' = (fromIntegral . ord) ch
    result <- g_unichar_validate ch'
    let result' = (/= 0) result
    return result'


-- function g_unichar_type
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "UnicodeType"
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_type" g_unichar_type :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CUInt


unicharType ::
    (MonadIO m) =>
    Char ->                                 -- c
    m UnicodeType
unicharType c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_type c'
    let result' = (toEnum . fromIntegral) result
    return result'


-- function g_unichar_toupper
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUniChar
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_toupper" g_unichar_toupper :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharToupper ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Char
unicharToupper c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_toupper c'
    let result' = (chr . fromIntegral) result
    return result'


-- function g_unichar_totitle
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUniChar
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_totitle" g_unichar_totitle :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharTotitle ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Char
unicharTotitle c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_totitle c'
    let result' = (chr . fromIntegral) result
    return result'


-- function g_unichar_tolower
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUniChar
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_tolower" g_unichar_tolower :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharTolower ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Char
unicharTolower c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_tolower c'
    let result' = (chr . fromIntegral) result
    return result'


-- function g_unichar_to_utf8
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "outbuf", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "outbuf", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_to_utf8" g_unichar_to_utf8 :: 
    CInt ->                                 -- c : TBasicType TUniChar
    CString ->                              -- outbuf : TBasicType TUTF8
    IO Int32


unicharToUtf8 ::
    (MonadIO m) =>
    Char ->                                 -- c
    T.Text ->                               -- outbuf
    m Int32
unicharToUtf8 c outbuf = liftIO $ do
    let c' = (fromIntegral . ord) c
    outbuf' <- textToCString outbuf
    result <- g_unichar_to_utf8 c' outbuf'
    freeMem outbuf'
    return result


-- function g_unichar_iszerowidth
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_iszerowidth" g_unichar_iszerowidth :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIszerowidth ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIszerowidth c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_iszerowidth c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_isxdigit
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_isxdigit" g_unichar_isxdigit :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsxdigit ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsxdigit c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_isxdigit c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_iswide_cjk
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_iswide_cjk" g_unichar_iswide_cjk :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIswideCjk ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIswideCjk c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_iswide_cjk c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_iswide
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_iswide" g_unichar_iswide :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIswide ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIswide c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_iswide c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_isupper
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_isupper" g_unichar_isupper :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsupper ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsupper c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_isupper c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_istitle
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_istitle" g_unichar_istitle :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIstitle ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIstitle c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_istitle c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_isspace
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_isspace" g_unichar_isspace :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsspace ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsspace c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_isspace c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_ispunct
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_ispunct" g_unichar_ispunct :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIspunct ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIspunct c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_ispunct c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_isprint
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_isprint" g_unichar_isprint :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsprint ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsprint c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_isprint c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_ismark
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_ismark" g_unichar_ismark :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsmark ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsmark c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_ismark c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_islower
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_islower" g_unichar_islower :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIslower ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIslower c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_islower c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_isgraph
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_isgraph" g_unichar_isgraph :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsgraph ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsgraph c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_isgraph c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_isdigit
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_isdigit" g_unichar_isdigit :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsdigit ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsdigit c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_isdigit c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_isdefined
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_isdefined" g_unichar_isdefined :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsdefined ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsdefined c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_isdefined c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_iscntrl
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_iscntrl" g_unichar_iscntrl :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIscntrl ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIscntrl c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_iscntrl c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_isalpha
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_isalpha" g_unichar_isalpha :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsalpha ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsalpha c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_isalpha c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_isalnum
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_isalnum" g_unichar_isalnum :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CInt


unicharIsalnum ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Bool
unicharIsalnum c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_isalnum c'
    let result' = (/= 0) result
    return result'


-- function g_unichar_get_script
-- Args : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "UnicodeScript"
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_get_script" g_unichar_get_script :: 
    CInt ->                                 -- ch : TBasicType TUniChar
    IO CUInt


unicharGetScript ::
    (MonadIO m) =>
    Char ->                                 -- ch
    m UnicodeScript
unicharGetScript ch = liftIO $ do
    let ch' = (fromIntegral . ord) ch
    result <- g_unichar_get_script ch'
    let result' = (toEnum . fromIntegral) result
    return result'


-- function g_unichar_get_mirror_char
-- Args : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mirrored_ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mirrored_ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_get_mirror_char" g_unichar_get_mirror_char :: 
    CInt ->                                 -- ch : TBasicType TUniChar
    CInt ->                                 -- mirrored_ch : TBasicType TUniChar
    IO CInt


unicharGetMirrorChar ::
    (MonadIO m) =>
    Char ->                                 -- ch
    Char ->                                 -- mirrored_ch
    m Bool
unicharGetMirrorChar ch mirrored_ch = liftIO $ do
    let ch' = (fromIntegral . ord) ch
    let mirrored_ch' = (fromIntegral . ord) mirrored_ch
    result <- g_unichar_get_mirror_char ch' mirrored_ch'
    let result' = (/= 0) result
    return result'


-- function g_unichar_digit_value
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_digit_value" g_unichar_digit_value :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO Int32


unicharDigitValue ::
    (MonadIO m) =>
    Char ->                                 -- c
    m Int32
unicharDigitValue c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_digit_value c'
    return result


-- function g_unichar_decompose
-- Args : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "a", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "b", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "a", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "b", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_decompose" g_unichar_decompose :: 
    CInt ->                                 -- ch : TBasicType TUniChar
    CInt ->                                 -- a : TBasicType TUniChar
    CInt ->                                 -- b : TBasicType TUniChar
    IO CInt


unicharDecompose ::
    (MonadIO m) =>
    Char ->                                 -- ch
    Char ->                                 -- a
    Char ->                                 -- b
    m Bool
unicharDecompose ch a b = liftIO $ do
    let ch' = (fromIntegral . ord) ch
    let a' = (fromIntegral . ord) a
    let b' = (fromIntegral . ord) b
    result <- g_unichar_decompose ch' a' b'
    let result' = (/= 0) result
    return result'


-- function g_unichar_compose
-- Args : [Arg {argName = "a", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "b", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "a", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "b", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ch", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_compose" g_unichar_compose :: 
    CInt ->                                 -- a : TBasicType TUniChar
    CInt ->                                 -- b : TBasicType TUniChar
    CInt ->                                 -- ch : TBasicType TUniChar
    IO CInt


unicharCompose ::
    (MonadIO m) =>
    Char ->                                 -- a
    Char ->                                 -- b
    Char ->                                 -- ch
    m Bool
unicharCompose a b ch = liftIO $ do
    let a' = (fromIntegral . ord) a
    let b' = (fromIntegral . ord) b
    let ch' = (fromIntegral . ord) ch
    result <- g_unichar_compose a' b' ch'
    let result' = (/= 0) result
    return result'


-- function g_unichar_combining_class
-- Args : [Arg {argName = "uc", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "uc", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_combining_class" g_unichar_combining_class :: 
    CInt ->                                 -- uc : TBasicType TUniChar
    IO Int32


unicharCombiningClass ::
    (MonadIO m) =>
    Char ->                                 -- uc
    m Int32
unicharCombiningClass uc = liftIO $ do
    let uc' = (fromIntegral . ord) uc
    result <- g_unichar_combining_class uc'
    return result


-- function g_unichar_break_type
-- Args : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "UnicodeBreakType"
-- throws : False
-- Skip return : False

foreign import ccall "g_unichar_break_type" g_unichar_break_type :: 
    CInt ->                                 -- c : TBasicType TUniChar
    IO CUInt


unicharBreakType ::
    (MonadIO m) =>
    Char ->                                 -- c
    m UnicodeBreakType
unicharBreakType c = liftIO $ do
    let c' = (fromIntegral . ord) c
    result <- g_unichar_break_type c'
    let result' = (toEnum . fromIntegral) result
    return result'


-- function g_trash_stack_push
-- Args : [Arg {argName = "stack_p", argType = TInterface "GLib" "TrashStack", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data_p", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "stack_p", argType = TInterface "GLib" "TrashStack", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data_p", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_trash_stack_push" g_trash_stack_push :: 
    Ptr TrashStack ->                       -- stack_p : TInterface "GLib" "TrashStack"
    Ptr () ->                               -- data_p : TBasicType TVoid
    IO ()


trashStackPush ::
    (MonadIO m) =>
    TrashStack ->                           -- stack_p
    Ptr () ->                               -- data_p
    m ()
trashStackPush stack_p data_p = liftIO $ do
    let stack_p' = unsafeManagedPtrGetPtr stack_p
    g_trash_stack_push stack_p' data_p
    touchManagedPtr stack_p
    return ()


-- function g_trash_stack_height
-- Args : [Arg {argName = "stack_p", argType = TInterface "GLib" "TrashStack", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "stack_p", argType = TInterface "GLib" "TrashStack", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_trash_stack_height" g_trash_stack_height :: 
    Ptr TrashStack ->                       -- stack_p : TInterface "GLib" "TrashStack"
    IO Word32


trashStackHeight ::
    (MonadIO m) =>
    TrashStack ->                           -- stack_p
    m Word32
trashStackHeight stack_p = liftIO $ do
    let stack_p' = unsafeManagedPtrGetPtr stack_p
    result <- g_trash_stack_height stack_p'
    touchManagedPtr stack_p
    return result


-- function g_timeout_source_new_seconds
-- Args : [Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "Source"
-- throws : False
-- Skip return : False

foreign import ccall "g_timeout_source_new_seconds" g_timeout_source_new_seconds :: 
    Word32 ->                               -- interval : TBasicType TUInt32
    IO (Ptr Source)


timeoutSourceNewSeconds ::
    (MonadIO m) =>
    Word32 ->                               -- interval
    m Source
timeoutSourceNewSeconds interval = liftIO $ do
    result <- g_timeout_source_new_seconds interval
    checkUnexpectedReturnNULL "g_timeout_source_new_seconds" result
    result' <- (wrapBoxed Source) result
    return result'


-- function g_timeout_source_new
-- Args : [Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "Source"
-- throws : False
-- Skip return : False

foreign import ccall "g_timeout_source_new" g_timeout_source_new :: 
    Word32 ->                               -- interval : TBasicType TUInt32
    IO (Ptr Source)


timeoutSourceNew ::
    (MonadIO m) =>
    Word32 ->                               -- interval
    m Source
timeoutSourceNew interval = liftIO $ do
    result <- g_timeout_source_new interval
    checkUnexpectedReturnNULL "g_timeout_source_new" result
    result' <- (wrapBoxed Source) result
    return result'


-- function g_timeout_add_seconds_full
-- Args : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "SourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "notify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "SourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_timeout_add_seconds_full" g_timeout_add_seconds_full :: 
    Int32 ->                                -- priority : TBasicType TInt32
    Word32 ->                               -- interval : TBasicType TUInt32
    FunPtr SourceFuncC ->                   -- function : TInterface "GLib" "SourceFunc"
    Ptr () ->                               -- data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- notify : TInterface "GLib" "DestroyNotify"
    IO Word32


timeoutAddSeconds ::
    (MonadIO m) =>
    Int32 ->                                -- priority
    Word32 ->                               -- interval
    SourceFunc ->                           -- function
    m Word32
timeoutAddSeconds priority interval function = liftIO $ do
    function' <- mkSourceFunc (sourceFuncWrapper Nothing function)
    let data_ = castFunPtrToPtr function'
    let notify = safeFreeFunPtrPtr
    result <- g_timeout_add_seconds_full priority interval function' data_ notify
    return result


-- function g_timeout_add_full
-- Args : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "SourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "notify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "SourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_timeout_add_full" g_timeout_add_full :: 
    Int32 ->                                -- priority : TBasicType TInt32
    Word32 ->                               -- interval : TBasicType TUInt32
    FunPtr SourceFuncC ->                   -- function : TInterface "GLib" "SourceFunc"
    Ptr () ->                               -- data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- notify : TInterface "GLib" "DestroyNotify"
    IO Word32


timeoutAdd ::
    (MonadIO m) =>
    Int32 ->                                -- priority
    Word32 ->                               -- interval
    SourceFunc ->                           -- function
    m Word32
timeoutAdd priority interval function = liftIO $ do
    function' <- mkSourceFunc (sourceFuncWrapper Nothing function)
    let data_ = castFunPtrToPtr function'
    let notify = safeFreeFunPtrPtr
    result <- g_timeout_add_full priority interval function' data_ notify
    return result


-- function g_time_val_from_iso8601
-- Args : [Arg {argName = "iso_date", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "time_", argType = TInterface "GLib" "TimeVal", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "iso_date", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_time_val_from_iso8601" g_time_val_from_iso8601 :: 
    CString ->                              -- iso_date : TBasicType TUTF8
    Ptr TimeVal ->                          -- time_ : TInterface "GLib" "TimeVal"
    IO CInt


timeValFromIso8601 ::
    (MonadIO m) =>
    T.Text ->                               -- iso_date
    m (Bool,TimeVal)
timeValFromIso8601 iso_date = liftIO $ do
    iso_date' <- textToCString iso_date
    time_ <- callocBytes 16 :: IO (Ptr TimeVal)
    result <- g_time_val_from_iso8601 iso_date' time_
    let result' = (/= 0) result
    time_' <- (wrapPtr TimeVal) time_
    freeMem iso_date'
    return (result', time_')


-- function g_thread_yield
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_yield" g_thread_yield :: 
    IO ()


threadYield ::
    (MonadIO m) =>
    m ()
threadYield  = liftIO $ do
    g_thread_yield
    return ()


-- function g_thread_self
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "GLib" "Thread"
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_self" g_thread_self :: 
    IO (Ptr Thread)


threadSelf ::
    (MonadIO m) =>
    m Thread
threadSelf  = liftIO $ do
    result <- g_thread_self
    checkUnexpectedReturnNULL "g_thread_self" result
    result' <- (wrapBoxed Thread) result
    return result'


-- function g_thread_pool_stop_unused_threads
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_pool_stop_unused_threads" g_thread_pool_stop_unused_threads :: 
    IO ()


threadPoolStopUnusedThreads ::
    (MonadIO m) =>
    m ()
threadPoolStopUnusedThreads  = liftIO $ do
    g_thread_pool_stop_unused_threads
    return ()


-- function g_thread_pool_set_max_unused_threads
-- Args : [Arg {argName = "max_threads", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "max_threads", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_pool_set_max_unused_threads" g_thread_pool_set_max_unused_threads :: 
    Int32 ->                                -- max_threads : TBasicType TInt32
    IO ()


threadPoolSetMaxUnusedThreads ::
    (MonadIO m) =>
    Int32 ->                                -- max_threads
    m ()
threadPoolSetMaxUnusedThreads max_threads = liftIO $ do
    g_thread_pool_set_max_unused_threads max_threads
    return ()


-- function g_thread_pool_set_max_idle_time
-- Args : [Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "interval", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_pool_set_max_idle_time" g_thread_pool_set_max_idle_time :: 
    Word32 ->                               -- interval : TBasicType TUInt32
    IO ()


threadPoolSetMaxIdleTime ::
    (MonadIO m) =>
    Word32 ->                               -- interval
    m ()
threadPoolSetMaxIdleTime interval = liftIO $ do
    g_thread_pool_set_max_idle_time interval
    return ()


-- function g_thread_pool_get_num_unused_threads
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_pool_get_num_unused_threads" g_thread_pool_get_num_unused_threads :: 
    IO Word32


threadPoolGetNumUnusedThreads ::
    (MonadIO m) =>
    m Word32
threadPoolGetNumUnusedThreads  = liftIO $ do
    result <- g_thread_pool_get_num_unused_threads
    return result


-- function g_thread_pool_get_max_unused_threads
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_pool_get_max_unused_threads" g_thread_pool_get_max_unused_threads :: 
    IO Int32


threadPoolGetMaxUnusedThreads ::
    (MonadIO m) =>
    m Int32
threadPoolGetMaxUnusedThreads  = liftIO $ do
    result <- g_thread_pool_get_max_unused_threads
    return result


-- function g_thread_pool_get_max_idle_time
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_pool_get_max_idle_time" g_thread_pool_get_max_idle_time :: 
    IO Word32


threadPoolGetMaxIdleTime ::
    (MonadIO m) =>
    m Word32
threadPoolGetMaxIdleTime  = liftIO $ do
    result <- g_thread_pool_get_max_idle_time
    return result


-- function g_thread_exit
-- Args : [Arg {argName = "retval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "retval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_exit" g_thread_exit :: 
    Ptr () ->                               -- retval : TBasicType TVoid
    IO ()


threadExit ::
    (MonadIO m) =>
    Ptr () ->                               -- retval
    m ()
threadExit retval = liftIO $ do
    g_thread_exit retval
    return ()


-- function g_thread_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_thread_error_quark" g_thread_error_quark :: 
    IO Word32


threadErrorQuark ::
    (MonadIO m) =>
    m Word32
threadErrorQuark  = liftIO $ do
    result <- g_thread_error_quark
    return result


-- function g_test_trap_subprocess
-- Args : [Arg {argName = "test_path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "usec_timeout", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_flags", argType = TInterface "GLib" "TestSubprocessFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "test_path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "usec_timeout", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_flags", argType = TInterface "GLib" "TestSubprocessFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_trap_subprocess" g_test_trap_subprocess :: 
    CString ->                              -- test_path : TBasicType TUTF8
    Word64 ->                               -- usec_timeout : TBasicType TUInt64
    CUInt ->                                -- test_flags : TInterface "GLib" "TestSubprocessFlags"
    IO ()


testTrapSubprocess ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- test_path
    Word64 ->                               -- usec_timeout
    [TestSubprocessFlags] ->                -- test_flags
    m ()
testTrapSubprocess test_path usec_timeout test_flags = liftIO $ do
    maybeTest_path <- case test_path of
        Nothing -> return nullPtr
        Just jTest_path -> do
            jTest_path' <- textToCString jTest_path
            return jTest_path'
    let test_flags' = gflagsToWord test_flags
    g_test_trap_subprocess maybeTest_path usec_timeout test_flags'
    freeMem maybeTest_path
    return ()


-- function g_test_trap_reached_timeout
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_test_trap_reached_timeout" g_test_trap_reached_timeout :: 
    IO CInt


testTrapReachedTimeout ::
    (MonadIO m) =>
    m Bool
testTrapReachedTimeout  = liftIO $ do
    result <- g_test_trap_reached_timeout
    let result' = (/= 0) result
    return result'


-- function g_test_trap_has_passed
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_test_trap_has_passed" g_test_trap_has_passed :: 
    IO CInt


testTrapHasPassed ::
    (MonadIO m) =>
    m Bool
testTrapHasPassed  = liftIO $ do
    result <- g_test_trap_has_passed
    let result' = (/= 0) result
    return result'


-- function g_test_trap_fork
-- Args : [Arg {argName = "usec_timeout", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_trap_flags", argType = TInterface "GLib" "TestTrapFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "usec_timeout", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_trap_flags", argType = TInterface "GLib" "TestTrapFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_test_trap_fork" g_test_trap_fork :: 
    Word64 ->                               -- usec_timeout : TBasicType TUInt64
    CUInt ->                                -- test_trap_flags : TInterface "GLib" "TestTrapFlags"
    IO CInt

{-# DEPRECATED testTrapFork ["This function is implemented only on Unix platforms,","and is not always reliable due to problems inherent in","fork-without-exec. Use g_test_trap_subprocess() instead."]#-}
testTrapFork ::
    (MonadIO m) =>
    Word64 ->                               -- usec_timeout
    [TestTrapFlags] ->                      -- test_trap_flags
    m Bool
testTrapFork usec_timeout test_trap_flags = liftIO $ do
    let test_trap_flags' = gflagsToWord test_trap_flags
    result <- g_test_trap_fork usec_timeout test_trap_flags'
    let result' = (/= 0) result
    return result'


-- function g_test_trap_assertions
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "assertion_flags", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "assertion_flags", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_trap_assertions" g_test_trap_assertions :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- file : TBasicType TUTF8
    Int32 ->                                -- line : TBasicType TInt32
    CString ->                              -- func : TBasicType TUTF8
    Word64 ->                               -- assertion_flags : TBasicType TUInt64
    CString ->                              -- pattern : TBasicType TUTF8
    IO ()


testTrapAssertions ::
    (MonadIO m) =>
    T.Text ->                               -- domain
    T.Text ->                               -- file
    Int32 ->                                -- line
    T.Text ->                               -- func
    Word64 ->                               -- assertion_flags
    T.Text ->                               -- pattern
    m ()
testTrapAssertions domain file line func assertion_flags pattern = liftIO $ do
    domain' <- textToCString domain
    file' <- textToCString file
    func' <- textToCString func
    pattern' <- textToCString pattern
    g_test_trap_assertions domain' file' line func' assertion_flags pattern'
    freeMem domain'
    freeMem file'
    freeMem func'
    freeMem pattern'
    return ()


-- function g_test_timer_start
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_timer_start" g_test_timer_start :: 
    IO ()


testTimerStart ::
    (MonadIO m) =>
    m ()
testTimerStart  = liftIO $ do
    g_test_timer_start
    return ()


-- function g_test_timer_last
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "g_test_timer_last" g_test_timer_last :: 
    IO CDouble


testTimerLast ::
    (MonadIO m) =>
    m Double
testTimerLast  = liftIO $ do
    result <- g_test_timer_last
    let result' = realToFrac result
    return result'


-- function g_test_timer_elapsed
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "g_test_timer_elapsed" g_test_timer_elapsed :: 
    IO CDouble


testTimerElapsed ::
    (MonadIO m) =>
    m Double
testTimerElapsed  = liftIO $ do
    result <- g_test_timer_elapsed
    let result' = realToFrac result
    return result'


-- function g_test_subprocess
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_test_subprocess" g_test_subprocess :: 
    IO CInt


testSubprocess ::
    (MonadIO m) =>
    m Bool
testSubprocess  = liftIO $ do
    result <- g_test_subprocess
    let result' = (/= 0) result
    return result'


-- function g_test_skip
-- Args : [Arg {argName = "msg", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "msg", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_skip" g_test_skip :: 
    CString ->                              -- msg : TBasicType TUTF8
    IO ()


testSkip ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- msg
    m ()
testSkip msg = liftIO $ do
    maybeMsg <- case msg of
        Nothing -> return nullPtr
        Just jMsg -> do
            jMsg' <- textToCString jMsg
            return jMsg'
    g_test_skip maybeMsg
    freeMem maybeMsg
    return ()


-- function g_test_set_nonfatal_assertions
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_set_nonfatal_assertions" g_test_set_nonfatal_assertions :: 
    IO ()


testSetNonfatalAssertions ::
    (MonadIO m) =>
    m ()
testSetNonfatalAssertions  = liftIO $ do
    g_test_set_nonfatal_assertions
    return ()


-- function g_test_run_suite
-- Args : [Arg {argName = "suite", argType = TInterface "GLib" "TestSuite", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "suite", argType = TInterface "GLib" "TestSuite", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_test_run_suite" g_test_run_suite :: 
    Ptr TestSuite ->                        -- suite : TInterface "GLib" "TestSuite"
    IO Int32


testRunSuite ::
    (MonadIO m) =>
    TestSuite ->                            -- suite
    m Int32
testRunSuite suite = liftIO $ do
    let suite' = unsafeManagedPtrGetPtr suite
    result <- g_test_run_suite suite'
    touchManagedPtr suite
    return result


-- function g_test_run
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_test_run" g_test_run :: 
    IO Int32


testRun ::
    (MonadIO m) =>
    m Int32
testRun  = liftIO $ do
    result <- g_test_run
    return result


-- function g_test_rand_int_range
-- Args : [Arg {argName = "begin", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "begin", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_test_rand_int_range" g_test_rand_int_range :: 
    Int32 ->                                -- begin : TBasicType TInt32
    Int32 ->                                -- end : TBasicType TInt32
    IO Int32


testRandIntRange ::
    (MonadIO m) =>
    Int32 ->                                -- begin
    Int32 ->                                -- end
    m Int32
testRandIntRange begin end = liftIO $ do
    result <- g_test_rand_int_range begin end
    return result


-- function g_test_rand_int
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_test_rand_int" g_test_rand_int :: 
    IO Int32


testRandInt ::
    (MonadIO m) =>
    m Int32
testRandInt  = liftIO $ do
    result <- g_test_rand_int
    return result


-- function g_test_rand_double_range
-- Args : [Arg {argName = "range_start", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "range_end", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "range_start", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "range_end", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "g_test_rand_double_range" g_test_rand_double_range :: 
    CDouble ->                              -- range_start : TBasicType TDouble
    CDouble ->                              -- range_end : TBasicType TDouble
    IO CDouble


testRandDoubleRange ::
    (MonadIO m) =>
    Double ->                               -- range_start
    Double ->                               -- range_end
    m Double
testRandDoubleRange range_start range_end = liftIO $ do
    let range_start' = realToFrac range_start
    let range_end' = realToFrac range_end
    result <- g_test_rand_double_range range_start' range_end'
    let result' = realToFrac result
    return result'


-- function g_test_rand_double
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "g_test_rand_double" g_test_rand_double :: 
    IO CDouble


testRandDouble ::
    (MonadIO m) =>
    m Double
testRandDouble  = liftIO $ do
    result <- g_test_rand_double
    let result' = realToFrac result
    return result'


-- function g_test_queue_free
-- Args : [Arg {argName = "gfree_pointer", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "gfree_pointer", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_queue_free" g_test_queue_free :: 
    Ptr () ->                               -- gfree_pointer : TBasicType TVoid
    IO ()


testQueueFree ::
    (MonadIO m) =>
    Ptr () ->                               -- gfree_pointer
    m ()
testQueueFree gfree_pointer = liftIO $ do
    g_test_queue_free gfree_pointer
    return ()


-- function g_test_queue_destroy
-- Args : [Arg {argName = "destroy_func", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "destroy_func", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_queue_destroy" g_test_queue_destroy :: 
    FunPtr DestroyNotifyC ->                -- destroy_func : TInterface "GLib" "DestroyNotify"
    Ptr () ->                               -- destroy_data : TBasicType TVoid
    IO ()


testQueueDestroy ::
    (MonadIO m) =>
    DestroyNotify ->                        -- destroy_func
    Ptr () ->                               -- destroy_data
    m ()
testQueueDestroy destroy_func destroy_data = liftIO $ do
    ptrdestroy_func <- callocMem :: IO (Ptr (FunPtr DestroyNotifyC))
    destroy_func' <- mkDestroyNotify (destroyNotifyWrapper (Just ptrdestroy_func) destroy_func)
    poke ptrdestroy_func destroy_func'
    g_test_queue_destroy destroy_func' destroy_data
    return ()


-- function g_test_log_type_name
-- Args : [Arg {argName = "log_type", argType = TInterface "GLib" "TestLogType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "log_type", argType = TInterface "GLib" "TestLogType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_test_log_type_name" g_test_log_type_name :: 
    CUInt ->                                -- log_type : TInterface "GLib" "TestLogType"
    IO CString


testLogTypeName ::
    (MonadIO m) =>
    TestLogType ->                          -- log_type
    m T.Text
testLogTypeName log_type = liftIO $ do
    let log_type' = (fromIntegral . fromEnum) log_type
    result <- g_test_log_type_name log_type'
    checkUnexpectedReturnNULL "g_test_log_type_name" result
    result' <- cstringToText result
    return result'


-- function g_test_incomplete
-- Args : [Arg {argName = "msg", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "msg", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_incomplete" g_test_incomplete :: 
    CString ->                              -- msg : TBasicType TUTF8
    IO ()


testIncomplete ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- msg
    m ()
testIncomplete msg = liftIO $ do
    maybeMsg <- case msg of
        Nothing -> return nullPtr
        Just jMsg -> do
            jMsg' <- textToCString jMsg
            return jMsg'
    g_test_incomplete maybeMsg
    freeMem maybeMsg
    return ()


-- function g_test_get_dir
-- Args : [Arg {argName = "file_type", argType = TInterface "GLib" "TestFileType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "file_type", argType = TInterface "GLib" "TestFileType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_test_get_dir" g_test_get_dir :: 
    CUInt ->                                -- file_type : TInterface "GLib" "TestFileType"
    IO CString


testGetDir ::
    (MonadIO m) =>
    TestFileType ->                         -- file_type
    m T.Text
testGetDir file_type = liftIO $ do
    let file_type' = (fromIntegral . fromEnum) file_type
    result <- g_test_get_dir file_type'
    checkUnexpectedReturnNULL "g_test_get_dir" result
    result' <- cstringToText result
    return result'


-- function g_test_failed
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_test_failed" g_test_failed :: 
    IO CInt


testFailed ::
    (MonadIO m) =>
    m Bool
testFailed  = liftIO $ do
    result <- g_test_failed
    let result' = (/= 0) result
    return result'


-- function g_test_fail
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_fail" g_test_fail :: 
    IO ()


testFail ::
    (MonadIO m) =>
    m ()
testFail  = liftIO $ do
    g_test_fail
    return ()


-- function g_test_expect_message
-- Args : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_level", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_level", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_expect_message" g_test_expect_message :: 
    CString ->                              -- log_domain : TBasicType TUTF8
    CUInt ->                                -- log_level : TInterface "GLib" "LogLevelFlags"
    CString ->                              -- pattern : TBasicType TUTF8
    IO ()


testExpectMessage ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- log_domain
    [LogLevelFlags] ->                      -- log_level
    T.Text ->                               -- pattern
    m ()
testExpectMessage log_domain log_level pattern = liftIO $ do
    maybeLog_domain <- case log_domain of
        Nothing -> return nullPtr
        Just jLog_domain -> do
            jLog_domain' <- textToCString jLog_domain
            return jLog_domain'
    let log_level' = gflagsToWord log_level
    pattern' <- textToCString pattern
    g_test_expect_message maybeLog_domain log_level' pattern'
    freeMem maybeLog_domain
    freeMem pattern'
    return ()


-- function g_test_bug_base
-- Args : [Arg {argName = "uri_pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "uri_pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_bug_base" g_test_bug_base :: 
    CString ->                              -- uri_pattern : TBasicType TUTF8
    IO ()


testBugBase ::
    (MonadIO m) =>
    T.Text ->                               -- uri_pattern
    m ()
testBugBase uri_pattern = liftIO $ do
    uri_pattern' <- textToCString uri_pattern
    g_test_bug_base uri_pattern'
    freeMem uri_pattern'
    return ()


-- function g_test_bug
-- Args : [Arg {argName = "bug_uri_snippet", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "bug_uri_snippet", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_bug" g_test_bug :: 
    CString ->                              -- bug_uri_snippet : TBasicType TUTF8
    IO ()


testBug ::
    (MonadIO m) =>
    T.Text ->                               -- bug_uri_snippet
    m ()
testBug bug_uri_snippet = liftIO $ do
    bug_uri_snippet' <- textToCString bug_uri_snippet
    g_test_bug bug_uri_snippet'
    freeMem bug_uri_snippet'
    return ()


-- function g_test_assert_expected_messages_internal
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_assert_expected_messages_internal" g_test_assert_expected_messages_internal :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- file : TBasicType TUTF8
    Int32 ->                                -- line : TBasicType TInt32
    CString ->                              -- func : TBasicType TUTF8
    IO ()


testAssertExpectedMessagesInternal ::
    (MonadIO m) =>
    T.Text ->                               -- domain
    T.Text ->                               -- file
    Int32 ->                                -- line
    T.Text ->                               -- func
    m ()
testAssertExpectedMessagesInternal domain file line func = liftIO $ do
    domain' <- textToCString domain
    file' <- textToCString file
    func' <- textToCString func
    g_test_assert_expected_messages_internal domain' file' line func'
    freeMem domain'
    freeMem file'
    freeMem func'
    return ()


-- function g_test_add_func
-- Args : [Arg {argName = "testpath", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_func", argType = TInterface "GLib" "TestFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "testpath", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_func", argType = TInterface "GLib" "TestFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_add_func" g_test_add_func :: 
    CString ->                              -- testpath : TBasicType TUTF8
    FunPtr TestFuncC ->                     -- test_func : TInterface "GLib" "TestFunc"
    IO ()


testAddFunc ::
    (MonadIO m) =>
    T.Text ->                               -- testpath
    TestFunc ->                             -- test_func
    m ()
testAddFunc testpath test_func = liftIO $ do
    testpath' <- textToCString testpath
    ptrtest_func <- callocMem :: IO (Ptr (FunPtr TestFuncC))
    test_func' <- mkTestFunc (testFuncWrapper (Just ptrtest_func) test_func)
    poke ptrtest_func test_func'
    g_test_add_func testpath' test_func'
    freeMem testpath'
    return ()


-- function g_test_add_data_func
-- Args : [Arg {argName = "testpath", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_func", argType = TInterface "GLib" "TestDataFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "testpath", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test_func", argType = TInterface "GLib" "TestDataFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_test_add_data_func" g_test_add_data_func :: 
    CString ->                              -- testpath : TBasicType TUTF8
    Ptr () ->                               -- test_data : TBasicType TVoid
    FunPtr TestDataFuncC ->                 -- test_func : TInterface "GLib" "TestDataFunc"
    IO ()


testAddDataFunc ::
    (MonadIO m) =>
    T.Text ->                               -- testpath
    Ptr () ->                               -- test_data
    TestDataFunc ->                         -- test_func
    m ()
testAddDataFunc testpath test_data test_func = liftIO $ do
    testpath' <- textToCString testpath
    ptrtest_func <- callocMem :: IO (Ptr (FunPtr TestDataFuncC))
    test_func' <- mkTestDataFunc (testDataFuncWrapper (Just ptrtest_func) test_func)
    poke ptrtest_func test_func'
    g_test_add_data_func testpath' test_data test_func'
    freeMem testpath'
    return ()


-- function g_strv_length
-- Args : [Arg {argName = "str_array", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str_array", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_strv_length" g_strv_length :: 
    CString ->                              -- str_array : TBasicType TUTF8
    IO Word32


strvLength ::
    (MonadIO m) =>
    T.Text ->                               -- str_array
    m Word32
strvLength str_array = liftIO $ do
    str_array' <- textToCString str_array
    result <- g_strv_length str_array'
    freeMem str_array'
    return result


-- function g_strv_get_type
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TGType
-- throws : False
-- Skip return : False

foreign import ccall "g_strv_get_type" g_strv_get_type :: 
    IO CGType


strvGetType ::
    (MonadIO m) =>
    m GType
strvGetType  = liftIO $ do
    result <- g_strv_get_type
    let result' = GType result
    return result'


-- function g_strv_contains
-- Args : [Arg {argName = "strv", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "strv", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_strv_contains" g_strv_contains :: 
    CString ->                              -- strv : TBasicType TUTF8
    CString ->                              -- str : TBasicType TUTF8
    IO CInt


strvContains ::
    (MonadIO m) =>
    T.Text ->                               -- strv
    T.Text ->                               -- str
    m Bool
strvContains strv str = liftIO $ do
    strv' <- textToCString strv
    str' <- textToCString str
    result <- g_strv_contains strv' str'
    let result' = (/= 0) result
    freeMem strv'
    freeMem str'
    return result'


-- function g_strup
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strup" g_strup :: 
    CString ->                              -- string : TBasicType TUTF8
    IO CString

{-# DEPRECATED strup ["(Since version 2.2)","This function is totally broken for the reasons","    discussed in the g_strncasecmp() docs - use g_ascii_strup()","    or g_utf8_strup() instead."]#-}
strup ::
    (MonadIO m) =>
    T.Text ->                               -- string
    m T.Text
strup string = liftIO $ do
    string' <- textToCString string
    result <- g_strup string'
    checkUnexpectedReturnNULL "g_strup" result
    result' <- cstringToText result
    freeMem result
    freeMem string'
    return result'


-- function g_strtod
-- Args : [Arg {argName = "nptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "nptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "g_strtod" g_strtod :: 
    CString ->                              -- nptr : TBasicType TUTF8
    CString ->                              -- endptr : TBasicType TUTF8
    IO CDouble


strtod ::
    (MonadIO m) =>
    T.Text ->                               -- nptr
    T.Text ->                               -- endptr
    m Double
strtod nptr endptr = liftIO $ do
    nptr' <- textToCString nptr
    endptr' <- textToCString endptr
    result <- g_strtod nptr' endptr'
    let result' = realToFrac result
    freeMem nptr'
    freeMem endptr'
    return result'


-- function g_strstr_len
-- Args : [Arg {argName = "haystack", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "haystack_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "needle", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "haystack", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "haystack_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "needle", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strstr_len" g_strstr_len :: 
    CString ->                              -- haystack : TBasicType TUTF8
    Int64 ->                                -- haystack_len : TBasicType TInt64
    CString ->                              -- needle : TBasicType TUTF8
    IO CString


strstrLen ::
    (MonadIO m) =>
    T.Text ->                               -- haystack
    Int64 ->                                -- haystack_len
    T.Text ->                               -- needle
    m T.Text
strstrLen haystack haystack_len needle = liftIO $ do
    haystack' <- textToCString haystack
    needle' <- textToCString needle
    result <- g_strstr_len haystack' haystack_len needle'
    checkUnexpectedReturnNULL "g_strstr_len" result
    result' <- cstringToText result
    freeMem result
    freeMem haystack'
    freeMem needle'
    return result'


-- function g_strsignal
-- Args : [Arg {argName = "signum", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "signum", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strsignal" g_strsignal :: 
    Int32 ->                                -- signum : TBasicType TInt32
    IO CString


strsignal ::
    (MonadIO m) =>
    Int32 ->                                -- signum
    m T.Text
strsignal signum = liftIO $ do
    result <- g_strsignal signum
    checkUnexpectedReturnNULL "g_strsignal" result
    result' <- cstringToText result
    return result'


-- function g_strrstr_len
-- Args : [Arg {argName = "haystack", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "haystack_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "needle", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "haystack", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "haystack_len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "needle", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strrstr_len" g_strrstr_len :: 
    CString ->                              -- haystack : TBasicType TUTF8
    Int64 ->                                -- haystack_len : TBasicType TInt64
    CString ->                              -- needle : TBasicType TUTF8
    IO CString


strrstrLen ::
    (MonadIO m) =>
    T.Text ->                               -- haystack
    Int64 ->                                -- haystack_len
    T.Text ->                               -- needle
    m T.Text
strrstrLen haystack haystack_len needle = liftIO $ do
    haystack' <- textToCString haystack
    needle' <- textToCString needle
    result <- g_strrstr_len haystack' haystack_len needle'
    checkUnexpectedReturnNULL "g_strrstr_len" result
    result' <- cstringToText result
    freeMem result
    freeMem haystack'
    freeMem needle'
    return result'


-- function g_strrstr
-- Args : [Arg {argName = "haystack", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "needle", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "haystack", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "needle", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strrstr" g_strrstr :: 
    CString ->                              -- haystack : TBasicType TUTF8
    CString ->                              -- needle : TBasicType TUTF8
    IO CString


strrstr ::
    (MonadIO m) =>
    T.Text ->                               -- haystack
    T.Text ->                               -- needle
    m T.Text
strrstr haystack needle = liftIO $ do
    haystack' <- textToCString haystack
    needle' <- textToCString needle
    result <- g_strrstr haystack' needle'
    checkUnexpectedReturnNULL "g_strrstr" result
    result' <- cstringToText result
    freeMem result
    freeMem haystack'
    freeMem needle'
    return result'


-- function g_strreverse
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strreverse" g_strreverse :: 
    CString ->                              -- string : TBasicType TUTF8
    IO CString


strreverse ::
    (MonadIO m) =>
    T.Text ->                               -- string
    m T.Text
strreverse string = liftIO $ do
    string' <- textToCString string
    result <- g_strreverse string'
    checkUnexpectedReturnNULL "g_strreverse" result
    result' <- cstringToText result
    freeMem result
    freeMem string'
    return result'


-- function g_strnfill
-- Args : [Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fill_char", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fill_char", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strnfill" g_strnfill :: 
    Word64 ->                               -- length : TBasicType TUInt64
    Int8 ->                                 -- fill_char : TBasicType TInt8
    IO CString


strnfill ::
    (MonadIO m) =>
    Word64 ->                               -- length
    Int8 ->                                 -- fill_char
    m T.Text
strnfill length_ fill_char = liftIO $ do
    result <- g_strnfill length_ fill_char
    checkUnexpectedReturnNULL "g_strnfill" result
    result' <- cstringToText result
    freeMem result
    return result'


-- function g_strndup
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strndup" g_strndup :: 
    CString ->                              -- str : TBasicType TUTF8
    Word64 ->                               -- n : TBasicType TUInt64
    IO CString


strndup ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Word64 ->                               -- n
    m T.Text
strndup str n = liftIO $ do
    str' <- textToCString str
    result <- g_strndup str' n
    checkUnexpectedReturnNULL "g_strndup" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_strncasecmp
-- Args : [Arg {argName = "s1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "s2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "s1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "s2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_strncasecmp" g_strncasecmp :: 
    CString ->                              -- s1 : TBasicType TUTF8
    CString ->                              -- s2 : TBasicType TUTF8
    Word32 ->                               -- n : TBasicType TUInt32
    IO Int32

{-# DEPRECATED strncasecmp ["(Since version 2.2)","The problem with g_strncasecmp() is that it does","    the comparison by calling toupper()/tolower(). These functions","    are locale-specific and operate on single bytes. However, it is","    impossible to handle things correctly from an internationalization","    standpoint by operating on bytes, since characters may be multibyte.","    Thus g_strncasecmp() is broken if your string is guaranteed to be","    ASCII, since it is locale-sensitive, and it's broken if your string","    is localized, since it doesn't work on many encodings at all,","    including UTF-8, EUC-JP, etc.","","    There are therefore two replacement techniques: g_ascii_strncasecmp(),","    which only works on ASCII and is not locale-sensitive, and","    g_utf8_casefold() followed by strcmp() on the resulting strings,","    which is good for case-insensitive sorting of UTF-8."]#-}
strncasecmp ::
    (MonadIO m) =>
    T.Text ->                               -- s1
    T.Text ->                               -- s2
    Word32 ->                               -- n
    m Int32
strncasecmp s1 s2 n = liftIO $ do
    s1' <- textToCString s1
    s2' <- textToCString s2
    result <- g_strncasecmp s1' s2' n
    freeMem s1'
    freeMem s2'
    return result


-- function g_strlcpy
-- Args : [Arg {argName = "dest", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dest", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_strlcpy" g_strlcpy :: 
    CString ->                              -- dest : TBasicType TUTF8
    CString ->                              -- src : TBasicType TUTF8
    Word64 ->                               -- dest_size : TBasicType TUInt64
    IO Word64


strlcpy ::
    (MonadIO m) =>
    T.Text ->                               -- dest
    T.Text ->                               -- src
    Word64 ->                               -- dest_size
    m Word64
strlcpy dest src dest_size = liftIO $ do
    dest' <- textToCString dest
    src' <- textToCString src
    result <- g_strlcpy dest' src' dest_size
    freeMem dest'
    freeMem src'
    return result


-- function g_strlcat
-- Args : [Arg {argName = "dest", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dest", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_strlcat" g_strlcat :: 
    CString ->                              -- dest : TBasicType TUTF8
    CString ->                              -- src : TBasicType TUTF8
    Word64 ->                               -- dest_size : TBasicType TUInt64
    IO Word64


strlcat ::
    (MonadIO m) =>
    T.Text ->                               -- dest
    T.Text ->                               -- src
    Word64 ->                               -- dest_size
    m Word64
strlcat dest src dest_size = liftIO $ do
    dest' <- textToCString dest
    src' <- textToCString src
    result <- g_strlcat dest' src' dest_size
    freeMem dest'
    freeMem src'
    return result


-- function g_strjoinv
-- Args : [Arg {argName = "separator", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str_array", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "separator", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str_array", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strjoinv" g_strjoinv :: 
    CString ->                              -- separator : TBasicType TUTF8
    CString ->                              -- str_array : TBasicType TUTF8
    IO CString


strjoinv ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- separator
    T.Text ->                               -- str_array
    m T.Text
strjoinv separator str_array = liftIO $ do
    maybeSeparator <- case separator of
        Nothing -> return nullPtr
        Just jSeparator -> do
            jSeparator' <- textToCString jSeparator
            return jSeparator'
    str_array' <- textToCString str_array
    result <- g_strjoinv maybeSeparator str_array'
    checkUnexpectedReturnNULL "g_strjoinv" result
    result' <- cstringToText result
    freeMem result
    freeMem maybeSeparator
    freeMem str_array'
    return result'


-- function g_strip_context
-- Args : [Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgval", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgval", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strip_context" g_strip_context :: 
    CString ->                              -- msgid : TBasicType TUTF8
    CString ->                              -- msgval : TBasicType TUTF8
    IO CString


stripContext ::
    (MonadIO m) =>
    T.Text ->                               -- msgid
    T.Text ->                               -- msgval
    m T.Text
stripContext msgid msgval = liftIO $ do
    msgid' <- textToCString msgid
    msgval' <- textToCString msgval
    result <- g_strip_context msgid' msgval'
    checkUnexpectedReturnNULL "g_strip_context" result
    result' <- cstringToText result
    freeMem msgid'
    freeMem msgval'
    return result'


-- function g_string_sized_new
-- Args : [Arg {argName = "dfl_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dfl_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "String"
-- throws : False
-- Skip return : False

foreign import ccall "g_string_sized_new" g_string_sized_new :: 
    Word64 ->                               -- dfl_size : TBasicType TUInt64
    IO (Ptr String)


stringSizedNew ::
    (MonadIO m) =>
    Word64 ->                               -- dfl_size
    m String
stringSizedNew dfl_size = liftIO $ do
    result <- g_string_sized_new dfl_size
    checkUnexpectedReturnNULL "g_string_sized_new" result
    result' <- (wrapBoxed String) result
    return result'


-- function g_string_new_len
-- Args : [Arg {argName = "init", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "init", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "String"
-- throws : False
-- Skip return : False

foreign import ccall "g_string_new_len" g_string_new_len :: 
    CString ->                              -- init : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO (Ptr String)


stringNewLen ::
    (MonadIO m) =>
    T.Text ->                               -- init
    Int64 ->                                -- len
    m String
stringNewLen init len = liftIO $ do
    init' <- textToCString init
    result <- g_string_new_len init' len
    checkUnexpectedReturnNULL "g_string_new_len" result
    result' <- (wrapBoxed String) result
    freeMem init'
    return result'


-- function g_string_new
-- Args : [Arg {argName = "init", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "init", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "String"
-- throws : False
-- Skip return : False

foreign import ccall "g_string_new" g_string_new :: 
    CString ->                              -- init : TBasicType TUTF8
    IO (Ptr String)


stringNew ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- init
    m String
stringNew init = liftIO $ do
    maybeInit <- case init of
        Nothing -> return nullPtr
        Just jInit -> do
            jInit' <- textToCString jInit
            return jInit'
    result <- g_string_new maybeInit
    checkUnexpectedReturnNULL "g_string_new" result
    result' <- (wrapBoxed String) result
    freeMem maybeInit
    return result'


-- function g_strfreev
-- Args : [Arg {argName = "str_array", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str_array", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_strfreev" g_strfreev :: 
    CString ->                              -- str_array : TBasicType TUTF8
    IO ()


strfreev ::
    (MonadIO m) =>
    T.Text ->                               -- str_array
    m ()
strfreev str_array = liftIO $ do
    str_array' <- textToCString str_array
    g_strfreev str_array'
    freeMem str_array'
    return ()


-- function g_strescape
-- Args : [Arg {argName = "source", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "exceptions", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "source", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "exceptions", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strescape" g_strescape :: 
    CString ->                              -- source : TBasicType TUTF8
    CString ->                              -- exceptions : TBasicType TUTF8
    IO CString


strescape ::
    (MonadIO m) =>
    T.Text ->                               -- source
    T.Text ->                               -- exceptions
    m T.Text
strescape source exceptions = liftIO $ do
    source' <- textToCString source
    exceptions' <- textToCString exceptions
    result <- g_strescape source' exceptions'
    checkUnexpectedReturnNULL "g_strescape" result
    result' <- cstringToText result
    freeMem result
    freeMem source'
    freeMem exceptions'
    return result'


-- function g_strerror
-- Args : [Arg {argName = "errnum", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "errnum", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strerror" g_strerror :: 
    Int32 ->                                -- errnum : TBasicType TInt32
    IO CString


strerror ::
    (MonadIO m) =>
    Int32 ->                                -- errnum
    m T.Text
strerror errnum = liftIO $ do
    result <- g_strerror errnum
    checkUnexpectedReturnNULL "g_strerror" result
    result' <- cstringToText result
    return result'


-- function g_strdup
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strdup" g_strdup :: 
    CString ->                              -- str : TBasicType TUTF8
    IO CString


strdup ::
    (MonadIO m) =>
    T.Text ->                               -- str
    m T.Text
strdup str = liftIO $ do
    str' <- textToCString str
    result <- g_strdup str'
    checkUnexpectedReturnNULL "g_strdup" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_strdown
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strdown" g_strdown :: 
    CString ->                              -- string : TBasicType TUTF8
    IO CString

{-# DEPRECATED strdown ["(Since version 2.2)","This function is totally broken for the reasons discussed","in the g_strncasecmp() docs - use g_ascii_strdown() or g_utf8_strdown()","instead."]#-}
strdown ::
    (MonadIO m) =>
    T.Text ->                               -- string
    m T.Text
strdown string = liftIO $ do
    string' <- textToCString string
    result <- g_strdown string'
    checkUnexpectedReturnNULL "g_strdown" result
    result' <- cstringToText result
    freeMem result
    freeMem string'
    return result'


-- function g_strdelimit
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "delimiters", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "new_delimiter", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "delimiters", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "new_delimiter", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strdelimit" g_strdelimit :: 
    CString ->                              -- string : TBasicType TUTF8
    CString ->                              -- delimiters : TBasicType TUTF8
    Int8 ->                                 -- new_delimiter : TBasicType TInt8
    IO CString


strdelimit ::
    (MonadIO m) =>
    T.Text ->                               -- string
    Maybe (T.Text) ->                       -- delimiters
    Int8 ->                                 -- new_delimiter
    m T.Text
strdelimit string delimiters new_delimiter = liftIO $ do
    string' <- textToCString string
    maybeDelimiters <- case delimiters of
        Nothing -> return nullPtr
        Just jDelimiters -> do
            jDelimiters' <- textToCString jDelimiters
            return jDelimiters'
    result <- g_strdelimit string' maybeDelimiters new_delimiter
    checkUnexpectedReturnNULL "g_strdelimit" result
    result' <- cstringToText result
    freeMem result
    freeMem string'
    freeMem maybeDelimiters
    return result'


-- function g_strcompress
-- Args : [Arg {argName = "source", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "source", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strcompress" g_strcompress :: 
    CString ->                              -- source : TBasicType TUTF8
    IO CString


strcompress ::
    (MonadIO m) =>
    T.Text ->                               -- source
    m T.Text
strcompress source = liftIO $ do
    source' <- textToCString source
    result <- g_strcompress source'
    checkUnexpectedReturnNULL "g_strcompress" result
    result' <- cstringToText result
    freeMem result
    freeMem source'
    return result'


-- function g_strcmp0
-- Args : [Arg {argName = "str1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_strcmp0" g_strcmp0 :: 
    CString ->                              -- str1 : TBasicType TUTF8
    CString ->                              -- str2 : TBasicType TUTF8
    IO Int32


strcmp0 ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- str1
    Maybe (T.Text) ->                       -- str2
    m Int32
strcmp0 str1 str2 = liftIO $ do
    maybeStr1 <- case str1 of
        Nothing -> return nullPtr
        Just jStr1 -> do
            jStr1' <- textToCString jStr1
            return jStr1'
    maybeStr2 <- case str2 of
        Nothing -> return nullPtr
        Just jStr2 -> do
            jStr2' <- textToCString jStr2
            return jStr2'
    result <- g_strcmp0 maybeStr1 maybeStr2
    freeMem maybeStr1
    freeMem maybeStr2
    return result


-- function g_strchug
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strchug" g_strchug :: 
    CString ->                              -- string : TBasicType TUTF8
    IO CString


strchug ::
    (MonadIO m) =>
    T.Text ->                               -- string
    m T.Text
strchug string = liftIO $ do
    string' <- textToCString string
    result <- g_strchug string'
    checkUnexpectedReturnNULL "g_strchug" result
    result' <- cstringToText result
    freeMem result
    freeMem string'
    return result'


-- function g_strchomp
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strchomp" g_strchomp :: 
    CString ->                              -- string : TBasicType TUTF8
    IO CString


strchomp ::
    (MonadIO m) =>
    T.Text ->                               -- string
    m T.Text
strchomp string = liftIO $ do
    string' <- textToCString string
    result <- g_strchomp string'
    checkUnexpectedReturnNULL "g_strchomp" result
    result' <- cstringToText result
    freeMem result
    freeMem string'
    return result'


-- function g_strcasecmp
-- Args : [Arg {argName = "s1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "s2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "s1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "s2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_strcasecmp" g_strcasecmp :: 
    CString ->                              -- s1 : TBasicType TUTF8
    CString ->                              -- s2 : TBasicType TUTF8
    IO Int32

{-# DEPRECATED strcasecmp ["(Since version 2.2)","See g_strncasecmp() for a discussion of why this","    function is deprecated and how to replace it."]#-}
strcasecmp ::
    (MonadIO m) =>
    T.Text ->                               -- s1
    T.Text ->                               -- s2
    m Int32
strcasecmp s1 s2 = liftIO $ do
    s1' <- textToCString s1
    s2' <- textToCString s2
    result <- g_strcasecmp s1' s2'
    freeMem s1'
    freeMem s2'
    return result


-- function g_strcanon
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "valid_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "substitutor", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "valid_chars", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "substitutor", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_strcanon" g_strcanon :: 
    CString ->                              -- string : TBasicType TUTF8
    CString ->                              -- valid_chars : TBasicType TUTF8
    Int8 ->                                 -- substitutor : TBasicType TInt8
    IO CString


strcanon ::
    (MonadIO m) =>
    T.Text ->                               -- string
    T.Text ->                               -- valid_chars
    Int8 ->                                 -- substitutor
    m T.Text
strcanon string valid_chars substitutor = liftIO $ do
    string' <- textToCString string
    valid_chars' <- textToCString valid_chars
    result <- g_strcanon string' valid_chars' substitutor
    checkUnexpectedReturnNULL "g_strcanon" result
    result' <- cstringToText result
    freeMem result
    freeMem string'
    freeMem valid_chars'
    return result'


-- function g_str_tokenize_and_fold
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "translit_locale", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ascii_alternates", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "translit_locale", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_str_tokenize_and_fold" g_str_tokenize_and_fold :: 
    CString ->                              -- string : TBasicType TUTF8
    CString ->                              -- translit_locale : TBasicType TUTF8
    Ptr (Ptr CString) ->                    -- ascii_alternates : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO (Ptr CString)


strTokenizeAndFold ::
    (MonadIO m) =>
    T.Text ->                               -- string
    Maybe (T.Text) ->                       -- translit_locale
    m ([T.Text],[T.Text])
strTokenizeAndFold string translit_locale = liftIO $ do
    string' <- textToCString string
    maybeTranslit_locale <- case translit_locale of
        Nothing -> return nullPtr
        Just jTranslit_locale -> do
            jTranslit_locale' <- textToCString jTranslit_locale
            return jTranslit_locale'
    ascii_alternates <- allocMem :: IO (Ptr (Ptr CString))
    result <- g_str_tokenize_and_fold string' maybeTranslit_locale ascii_alternates
    checkUnexpectedReturnNULL "g_str_tokenize_and_fold" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    ascii_alternates' <- peek ascii_alternates
    ascii_alternates'' <- unpackZeroTerminatedUTF8CArray ascii_alternates'
    mapZeroTerminatedCArray freeMem ascii_alternates'
    freeMem ascii_alternates'
    freeMem string'
    freeMem maybeTranslit_locale
    freeMem ascii_alternates
    return (result', ascii_alternates'')


-- function g_str_to_ascii
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "from_locale", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "from_locale", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_str_to_ascii" g_str_to_ascii :: 
    CString ->                              -- str : TBasicType TUTF8
    CString ->                              -- from_locale : TBasicType TUTF8
    IO CString


strToAscii ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Maybe (T.Text) ->                       -- from_locale
    m T.Text
strToAscii str from_locale = liftIO $ do
    str' <- textToCString str
    maybeFrom_locale <- case from_locale of
        Nothing -> return nullPtr
        Just jFrom_locale -> do
            jFrom_locale' <- textToCString jFrom_locale
            return jFrom_locale'
    result <- g_str_to_ascii str' maybeFrom_locale
    checkUnexpectedReturnNULL "g_str_to_ascii" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    freeMem maybeFrom_locale
    return result'


-- function g_str_match_string
-- Args : [Arg {argName = "search_term", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "potential_hit", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accept_alternates", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "search_term", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "potential_hit", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "accept_alternates", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_str_match_string" g_str_match_string :: 
    CString ->                              -- search_term : TBasicType TUTF8
    CString ->                              -- potential_hit : TBasicType TUTF8
    CInt ->                                 -- accept_alternates : TBasicType TBoolean
    IO CInt


strMatchString ::
    (MonadIO m) =>
    T.Text ->                               -- search_term
    T.Text ->                               -- potential_hit
    Bool ->                                 -- accept_alternates
    m Bool
strMatchString search_term potential_hit accept_alternates = liftIO $ do
    search_term' <- textToCString search_term
    potential_hit' <- textToCString potential_hit
    let accept_alternates' = (fromIntegral . fromEnum) accept_alternates
    result <- g_str_match_string search_term' potential_hit' accept_alternates'
    let result' = (/= 0) result
    freeMem search_term'
    freeMem potential_hit'
    return result'


-- function g_str_is_ascii
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_str_is_ascii" g_str_is_ascii :: 
    CString ->                              -- str : TBasicType TUTF8
    IO CInt


strIsAscii ::
    (MonadIO m) =>
    T.Text ->                               -- str
    m Bool
strIsAscii str = liftIO $ do
    str' <- textToCString str
    result <- g_str_is_ascii str'
    let result' = (/= 0) result
    freeMem str'
    return result'


-- function g_str_hash
-- Args : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_str_hash" g_str_hash :: 
    Ptr () ->                               -- v : TBasicType TVoid
    IO Word32


strHash ::
    (MonadIO m) =>
    Ptr () ->                               -- v
    m Word32
strHash v = liftIO $ do
    result <- g_str_hash v
    return result


-- function g_str_has_suffix
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "suffix", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "suffix", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_str_has_suffix" g_str_has_suffix :: 
    CString ->                              -- str : TBasicType TUTF8
    CString ->                              -- suffix : TBasicType TUTF8
    IO CInt


strHasSuffix ::
    (MonadIO m) =>
    T.Text ->                               -- str
    T.Text ->                               -- suffix
    m Bool
strHasSuffix str suffix = liftIO $ do
    str' <- textToCString str
    suffix' <- textToCString suffix
    result <- g_str_has_suffix str' suffix'
    let result' = (/= 0) result
    freeMem str'
    freeMem suffix'
    return result'


-- function g_str_has_prefix
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "prefix", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "prefix", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_str_has_prefix" g_str_has_prefix :: 
    CString ->                              -- str : TBasicType TUTF8
    CString ->                              -- prefix : TBasicType TUTF8
    IO CInt


strHasPrefix ::
    (MonadIO m) =>
    T.Text ->                               -- str
    T.Text ->                               -- prefix
    m Bool
strHasPrefix str prefix = liftIO $ do
    str' <- textToCString str
    prefix' <- textToCString prefix
    result <- g_str_has_prefix str' prefix'
    let result' = (/= 0) result
    freeMem str'
    freeMem prefix'
    return result'


-- function g_str_equal
-- Args : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_str_equal" g_str_equal :: 
    Ptr () ->                               -- v1 : TBasicType TVoid
    Ptr () ->                               -- v2 : TBasicType TVoid
    IO CInt


strEqual ::
    (MonadIO m) =>
    Ptr () ->                               -- v1
    Ptr () ->                               -- v2
    m Bool
strEqual v1 v2 = liftIO $ do
    result <- g_str_equal v1 v2
    let result' = (/= 0) result
    return result'


-- function g_stpcpy
-- Args : [Arg {argName = "dest", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dest", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_stpcpy" g_stpcpy :: 
    CString ->                              -- dest : TBasicType TUTF8
    CString ->                              -- src : TBasicType TUTF8
    IO CString


stpcpy ::
    (MonadIO m) =>
    T.Text ->                               -- dest
    T.Text ->                               -- src
    m T.Text
stpcpy dest src = liftIO $ do
    dest' <- textToCString dest
    src' <- textToCString src
    result <- g_stpcpy dest' src'
    checkUnexpectedReturnNULL "g_stpcpy" result
    result' <- cstringToText result
    freeMem result
    freeMem dest'
    freeMem src'
    return result'


-- function g_spawn_sync
-- Args : [Arg {argName = "working_directory", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "argv", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "GLib" "SpawnFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_setup", argType = TInterface "GLib" "SpawnChildSetupFunc", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "standard_output", argType = TCArray True (-1) (-1) (TBasicType TUInt8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "standard_error", argType = TCArray True (-1) (-1) (TBasicType TUInt8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "exit_status", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "working_directory", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "argv", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "GLib" "SpawnFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_setup", argType = TInterface "GLib" "SpawnChildSetupFunc", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_spawn_sync" g_spawn_sync :: 
    CString ->                              -- working_directory : TBasicType TUTF8
    Ptr CString ->                          -- argv : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr CString ->                          -- envp : TCArray True (-1) (-1) (TBasicType TUTF8)
    CUInt ->                                -- flags : TInterface "GLib" "SpawnFlags"
    FunPtr SpawnChildSetupFuncC ->          -- child_setup : TInterface "GLib" "SpawnChildSetupFunc"
    Ptr () ->                               -- user_data : TBasicType TVoid
    Ptr (Ptr Word8) ->                      -- standard_output : TCArray True (-1) (-1) (TBasicType TUInt8)
    Ptr (Ptr Word8) ->                      -- standard_error : TCArray True (-1) (-1) (TBasicType TUInt8)
    Ptr Int32 ->                            -- exit_status : TBasicType TInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt


spawnSync ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- working_directory
    [T.Text] ->                             -- argv
    Maybe ([T.Text]) ->                     -- envp
    [SpawnFlags] ->                         -- flags
    Maybe (SpawnChildSetupFunc) ->          -- child_setup
    m (ByteString,ByteString,Int32)
spawnSync working_directory argv envp flags child_setup = liftIO $ do
    maybeWorking_directory <- case working_directory of
        Nothing -> return nullPtr
        Just jWorking_directory -> do
            jWorking_directory' <- textToCString jWorking_directory
            return jWorking_directory'
    argv' <- packZeroTerminatedUTF8CArray argv
    maybeEnvp <- case envp of
        Nothing -> return nullPtr
        Just jEnvp -> do
            jEnvp' <- packZeroTerminatedUTF8CArray jEnvp
            return jEnvp'
    let flags' = gflagsToWord flags
    ptrchild_setup <- callocMem :: IO (Ptr (FunPtr SpawnChildSetupFuncC))
    maybeChild_setup <- case child_setup of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jChild_setup -> do
            jChild_setup' <- mkSpawnChildSetupFunc (spawnChildSetupFuncWrapper (Just ptrchild_setup) jChild_setup)
            poke ptrchild_setup jChild_setup'
            return jChild_setup'
    standard_output <- allocMem :: IO (Ptr (Ptr Word8))
    standard_error <- allocMem :: IO (Ptr (Ptr Word8))
    exit_status <- allocMem :: IO (Ptr Int32)
    let user_data = nullPtr
    onException (do
        _ <- propagateGError $ g_spawn_sync maybeWorking_directory argv' maybeEnvp flags' maybeChild_setup user_data standard_output standard_error exit_status
        standard_output' <- peek standard_output
        standard_output'' <- unpackZeroTerminatedByteString standard_output'
        freeMem standard_output'
        standard_error' <- peek standard_error
        standard_error'' <- unpackZeroTerminatedByteString standard_error'
        freeMem standard_error'
        exit_status' <- peek exit_status
        freeMem maybeWorking_directory
        mapZeroTerminatedCArray freeMem argv'
        freeMem argv'
        mapZeroTerminatedCArray freeMem maybeEnvp
        freeMem maybeEnvp
        freeMem standard_output
        freeMem standard_error
        freeMem exit_status
        return (standard_output'', standard_error'', exit_status')
     ) (do
        freeMem maybeWorking_directory
        mapZeroTerminatedCArray freeMem argv'
        freeMem argv'
        mapZeroTerminatedCArray freeMem maybeEnvp
        freeMem maybeEnvp
        freeMem standard_output
        freeMem standard_error
        freeMem exit_status
     )


-- function g_spawn_exit_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_spawn_exit_error_quark" g_spawn_exit_error_quark :: 
    IO Word32


spawnExitErrorQuark ::
    (MonadIO m) =>
    m Word32
spawnExitErrorQuark  = liftIO $ do
    result <- g_spawn_exit_error_quark
    return result


-- function g_spawn_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_spawn_error_quark" g_spawn_error_quark :: 
    IO Word32


spawnErrorQuark ::
    (MonadIO m) =>
    m Word32
spawnErrorQuark  = liftIO $ do
    result <- g_spawn_error_quark
    return result


-- function g_spawn_command_line_sync
-- Args : [Arg {argName = "command_line", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "standard_output", argType = TCArray True (-1) (-1) (TBasicType TUInt8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "standard_error", argType = TCArray True (-1) (-1) (TBasicType TUInt8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "exit_status", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "command_line", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_spawn_command_line_sync" g_spawn_command_line_sync :: 
    CString ->                              -- command_line : TBasicType TUTF8
    Ptr (Ptr Word8) ->                      -- standard_output : TCArray True (-1) (-1) (TBasicType TUInt8)
    Ptr (Ptr Word8) ->                      -- standard_error : TCArray True (-1) (-1) (TBasicType TUInt8)
    Ptr Int32 ->                            -- exit_status : TBasicType TInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt


spawnCommandLineSync ::
    (MonadIO m) =>
    T.Text ->                               -- command_line
    m (ByteString,ByteString,Int32)
spawnCommandLineSync command_line = liftIO $ do
    command_line' <- textToCString command_line
    standard_output <- allocMem :: IO (Ptr (Ptr Word8))
    standard_error <- allocMem :: IO (Ptr (Ptr Word8))
    exit_status <- allocMem :: IO (Ptr Int32)
    onException (do
        _ <- propagateGError $ g_spawn_command_line_sync command_line' standard_output standard_error exit_status
        standard_output' <- peek standard_output
        standard_output'' <- unpackZeroTerminatedByteString standard_output'
        freeMem standard_output'
        standard_error' <- peek standard_error
        standard_error'' <- unpackZeroTerminatedByteString standard_error'
        freeMem standard_error'
        exit_status' <- peek exit_status
        freeMem command_line'
        freeMem standard_output
        freeMem standard_error
        freeMem exit_status
        return (standard_output'', standard_error'', exit_status')
     ) (do
        freeMem command_line'
        freeMem standard_output
        freeMem standard_error
        freeMem exit_status
     )


-- function g_spawn_command_line_async
-- Args : [Arg {argName = "command_line", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "command_line", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_spawn_command_line_async" g_spawn_command_line_async :: 
    CString ->                              -- command_line : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt


spawnCommandLineAsync ::
    (MonadIO m) =>
    T.Text ->                               -- command_line
    m ()
spawnCommandLineAsync command_line = liftIO $ do
    command_line' <- textToCString command_line
    onException (do
        _ <- propagateGError $ g_spawn_command_line_async command_line'
        freeMem command_line'
        return ()
     ) (do
        freeMem command_line'
     )


-- function g_spawn_close_pid
-- Args : [Arg {argName = "pid", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pid", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_spawn_close_pid" g_spawn_close_pid :: 
    Int32 ->                                -- pid : TBasicType TInt32
    IO ()


spawnClosePid ::
    (MonadIO m) =>
    Int32 ->                                -- pid
    m ()
spawnClosePid pid = liftIO $ do
    g_spawn_close_pid pid
    return ()


-- function g_spawn_check_exit_status
-- Args : [Arg {argName = "exit_status", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "exit_status", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_spawn_check_exit_status" g_spawn_check_exit_status :: 
    Int32 ->                                -- exit_status : TBasicType TInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt


spawnCheckExitStatus ::
    (MonadIO m) =>
    Int32 ->                                -- exit_status
    m ()
spawnCheckExitStatus exit_status = liftIO $ do
    onException (do
        _ <- propagateGError $ g_spawn_check_exit_status exit_status
        return ()
     ) (do
        return ()
     )


-- function g_spawn_async_with_pipes
-- Args : [Arg {argName = "working_directory", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "argv", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "GLib" "SpawnFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_setup", argType = TInterface "GLib" "SpawnChildSetupFunc", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_pid", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "standard_input", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "standard_output", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "standard_error", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "working_directory", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "argv", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "GLib" "SpawnFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_setup", argType = TInterface "GLib" "SpawnChildSetupFunc", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_spawn_async_with_pipes" g_spawn_async_with_pipes :: 
    CString ->                              -- working_directory : TBasicType TUTF8
    Ptr CString ->                          -- argv : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr CString ->                          -- envp : TCArray True (-1) (-1) (TBasicType TUTF8)
    CUInt ->                                -- flags : TInterface "GLib" "SpawnFlags"
    FunPtr SpawnChildSetupFuncC ->          -- child_setup : TInterface "GLib" "SpawnChildSetupFunc"
    Ptr () ->                               -- user_data : TBasicType TVoid
    Ptr Int32 ->                            -- child_pid : TBasicType TInt32
    Ptr Int32 ->                            -- standard_input : TBasicType TInt32
    Ptr Int32 ->                            -- standard_output : TBasicType TInt32
    Ptr Int32 ->                            -- standard_error : TBasicType TInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt


spawnAsyncWithPipes ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- working_directory
    [T.Text] ->                             -- argv
    Maybe ([T.Text]) ->                     -- envp
    [SpawnFlags] ->                         -- flags
    Maybe (SpawnChildSetupFunc) ->          -- child_setup
    m (Int32,Int32,Int32,Int32)
spawnAsyncWithPipes working_directory argv envp flags child_setup = liftIO $ do
    maybeWorking_directory <- case working_directory of
        Nothing -> return nullPtr
        Just jWorking_directory -> do
            jWorking_directory' <- textToCString jWorking_directory
            return jWorking_directory'
    argv' <- packZeroTerminatedUTF8CArray argv
    maybeEnvp <- case envp of
        Nothing -> return nullPtr
        Just jEnvp -> do
            jEnvp' <- packZeroTerminatedUTF8CArray jEnvp
            return jEnvp'
    let flags' = gflagsToWord flags
    ptrchild_setup <- callocMem :: IO (Ptr (FunPtr SpawnChildSetupFuncC))
    maybeChild_setup <- case child_setup of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jChild_setup -> do
            jChild_setup' <- mkSpawnChildSetupFunc (spawnChildSetupFuncWrapper (Just ptrchild_setup) jChild_setup)
            poke ptrchild_setup jChild_setup'
            return jChild_setup'
    child_pid <- allocMem :: IO (Ptr Int32)
    standard_input <- allocMem :: IO (Ptr Int32)
    standard_output <- allocMem :: IO (Ptr Int32)
    standard_error <- allocMem :: IO (Ptr Int32)
    let user_data = nullPtr
    onException (do
        _ <- propagateGError $ g_spawn_async_with_pipes maybeWorking_directory argv' maybeEnvp flags' maybeChild_setup user_data child_pid standard_input standard_output standard_error
        child_pid' <- peek child_pid
        standard_input' <- peek standard_input
        standard_output' <- peek standard_output
        standard_error' <- peek standard_error
        freeMem maybeWorking_directory
        mapZeroTerminatedCArray freeMem argv'
        freeMem argv'
        mapZeroTerminatedCArray freeMem maybeEnvp
        freeMem maybeEnvp
        freeMem child_pid
        freeMem standard_input
        freeMem standard_output
        freeMem standard_error
        return (child_pid', standard_input', standard_output', standard_error')
     ) (do
        freeMem maybeWorking_directory
        mapZeroTerminatedCArray freeMem argv'
        freeMem argv'
        mapZeroTerminatedCArray freeMem maybeEnvp
        freeMem maybeEnvp
        freeMem child_pid
        freeMem standard_input
        freeMem standard_output
        freeMem standard_error
     )


-- function g_spawn_async
-- Args : [Arg {argName = "working_directory", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "argv", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "GLib" "SpawnFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_setup", argType = TInterface "GLib" "SpawnChildSetupFunc", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_pid", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "working_directory", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "argv", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "GLib" "SpawnFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "child_setup", argType = TInterface "GLib" "SpawnChildSetupFunc", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = 5, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_spawn_async" g_spawn_async :: 
    CString ->                              -- working_directory : TBasicType TUTF8
    Ptr CString ->                          -- argv : TCArray True (-1) (-1) (TBasicType TUTF8)
    Ptr CString ->                          -- envp : TCArray True (-1) (-1) (TBasicType TUTF8)
    CUInt ->                                -- flags : TInterface "GLib" "SpawnFlags"
    FunPtr SpawnChildSetupFuncC ->          -- child_setup : TInterface "GLib" "SpawnChildSetupFunc"
    Ptr () ->                               -- user_data : TBasicType TVoid
    Ptr Int32 ->                            -- child_pid : TBasicType TInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt


spawnAsync ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- working_directory
    [T.Text] ->                             -- argv
    Maybe ([T.Text]) ->                     -- envp
    [SpawnFlags] ->                         -- flags
    Maybe (SpawnChildSetupFunc) ->          -- child_setup
    m (Int32)
spawnAsync working_directory argv envp flags child_setup = liftIO $ do
    maybeWorking_directory <- case working_directory of
        Nothing -> return nullPtr
        Just jWorking_directory -> do
            jWorking_directory' <- textToCString jWorking_directory
            return jWorking_directory'
    argv' <- packZeroTerminatedUTF8CArray argv
    maybeEnvp <- case envp of
        Nothing -> return nullPtr
        Just jEnvp -> do
            jEnvp' <- packZeroTerminatedUTF8CArray jEnvp
            return jEnvp'
    let flags' = gflagsToWord flags
    ptrchild_setup <- callocMem :: IO (Ptr (FunPtr SpawnChildSetupFuncC))
    maybeChild_setup <- case child_setup of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jChild_setup -> do
            jChild_setup' <- mkSpawnChildSetupFunc (spawnChildSetupFuncWrapper (Just ptrchild_setup) jChild_setup)
            poke ptrchild_setup jChild_setup'
            return jChild_setup'
    child_pid <- allocMem :: IO (Ptr Int32)
    let user_data = nullPtr
    onException (do
        _ <- propagateGError $ g_spawn_async maybeWorking_directory argv' maybeEnvp flags' maybeChild_setup user_data child_pid
        child_pid' <- peek child_pid
        freeMem maybeWorking_directory
        mapZeroTerminatedCArray freeMem argv'
        freeMem argv'
        mapZeroTerminatedCArray freeMem maybeEnvp
        freeMem maybeEnvp
        freeMem child_pid
        return child_pid'
     ) (do
        freeMem maybeWorking_directory
        mapZeroTerminatedCArray freeMem argv'
        freeMem argv'
        mapZeroTerminatedCArray freeMem maybeEnvp
        freeMem maybeEnvp
        freeMem child_pid
     )


-- function g_spaced_primes_closest
-- Args : [Arg {argName = "num", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "num", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_spaced_primes_closest" g_spaced_primes_closest :: 
    Word32 ->                               -- num : TBasicType TUInt32
    IO Word32


spacedPrimesClosest ::
    (MonadIO m) =>
    Word32 ->                               -- num
    m Word32
spacedPrimesClosest num = liftIO $ do
    result <- g_spaced_primes_closest num
    return result


-- function g_source_set_name_by_id
-- Args : [Arg {argName = "tag", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "tag", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_source_set_name_by_id" g_source_set_name_by_id :: 
    Word32 ->                               -- tag : TBasicType TUInt32
    CString ->                              -- name : TBasicType TUTF8
    IO ()


sourceSetNameById ::
    (MonadIO m) =>
    Word32 ->                               -- tag
    T.Text ->                               -- name
    m ()
sourceSetNameById tag name = liftIO $ do
    name' <- textToCString name
    g_source_set_name_by_id tag name'
    freeMem name'
    return ()


-- function g_source_remove_by_user_data
-- Args : [Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_source_remove_by_user_data" g_source_remove_by_user_data :: 
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO CInt


sourceRemoveByUserData ::
    (MonadIO m) =>
    Ptr () ->                               -- user_data
    m Bool
sourceRemoveByUserData user_data = liftIO $ do
    result <- g_source_remove_by_user_data user_data
    let result' = (/= 0) result
    return result'


-- function g_source_remove_by_funcs_user_data
-- Args : [Arg {argName = "funcs", argType = TInterface "GLib" "SourceFuncs", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "funcs", argType = TInterface "GLib" "SourceFuncs", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_source_remove_by_funcs_user_data" g_source_remove_by_funcs_user_data :: 
    Ptr SourceFuncs ->                      -- funcs : TInterface "GLib" "SourceFuncs"
    Ptr () ->                               -- user_data : TBasicType TVoid
    IO CInt


sourceRemoveByFuncsUserData ::
    (MonadIO m) =>
    SourceFuncs ->                          -- funcs
    Ptr () ->                               -- user_data
    m Bool
sourceRemoveByFuncsUserData funcs user_data = liftIO $ do
    let funcs' = unsafeManagedPtrGetPtr funcs
    result <- g_source_remove_by_funcs_user_data funcs' user_data
    let result' = (/= 0) result
    touchManagedPtr funcs
    return result'


-- function g_source_remove
-- Args : [Arg {argName = "tag", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "tag", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_source_remove" g_source_remove :: 
    Word32 ->                               -- tag : TBasicType TUInt32
    IO CInt


sourceRemove ::
    (MonadIO m) =>
    Word32 ->                               -- tag
    m Bool
sourceRemove tag = liftIO $ do
    result <- g_source_remove tag
    let result' = (/= 0) result
    return result'


-- function g_slice_set_config
-- Args : [Arg {argName = "ckey", argType = TInterface "GLib" "SliceConfig", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "ckey", argType = TInterface "GLib" "SliceConfig", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_slice_set_config" g_slice_set_config :: 
    CUInt ->                                -- ckey : TInterface "GLib" "SliceConfig"
    Int64 ->                                -- value : TBasicType TInt64
    IO ()


sliceSetConfig ::
    (MonadIO m) =>
    SliceConfig ->                          -- ckey
    Int64 ->                                -- value
    m ()
sliceSetConfig ckey value = liftIO $ do
    let ckey' = (fromIntegral . fromEnum) ckey
    g_slice_set_config ckey' value
    return ()


-- function g_slice_get_config_state
-- Args : [Arg {argName = "ckey", argType = TInterface "GLib" "SliceConfig", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "address", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n_values", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "ckey", argType = TInterface "GLib" "SliceConfig", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "address", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n_values", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_slice_get_config_state" g_slice_get_config_state :: 
    CUInt ->                                -- ckey : TInterface "GLib" "SliceConfig"
    Int64 ->                                -- address : TBasicType TInt64
    Word32 ->                               -- n_values : TBasicType TUInt32
    IO Int64


sliceGetConfigState ::
    (MonadIO m) =>
    SliceConfig ->                          -- ckey
    Int64 ->                                -- address
    Word32 ->                               -- n_values
    m Int64
sliceGetConfigState ckey address n_values = liftIO $ do
    let ckey' = (fromIntegral . fromEnum) ckey
    result <- g_slice_get_config_state ckey' address n_values
    return result


-- function g_slice_get_config
-- Args : [Arg {argName = "ckey", argType = TInterface "GLib" "SliceConfig", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "ckey", argType = TInterface "GLib" "SliceConfig", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_slice_get_config" g_slice_get_config :: 
    CUInt ->                                -- ckey : TInterface "GLib" "SliceConfig"
    IO Int64


sliceGetConfig ::
    (MonadIO m) =>
    SliceConfig ->                          -- ckey
    m Int64
sliceGetConfig ckey = liftIO $ do
    let ckey' = (fromIntegral . fromEnum) ckey
    result <- g_slice_get_config ckey'
    return result


-- function g_slice_free_chain_with_offset
-- Args : [Arg {argName = "block_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mem_chain", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "next_offset", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "block_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mem_chain", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "next_offset", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_slice_free_chain_with_offset" g_slice_free_chain_with_offset :: 
    Word64 ->                               -- block_size : TBasicType TUInt64
    Ptr () ->                               -- mem_chain : TBasicType TVoid
    Word64 ->                               -- next_offset : TBasicType TUInt64
    IO ()


sliceFreeChainWithOffset ::
    (MonadIO m) =>
    Word64 ->                               -- block_size
    Ptr () ->                               -- mem_chain
    Word64 ->                               -- next_offset
    m ()
sliceFreeChainWithOffset block_size mem_chain next_offset = liftIO $ do
    g_slice_free_chain_with_offset block_size mem_chain next_offset
    return ()


-- function g_slice_free1
-- Args : [Arg {argName = "block_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mem_block", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "block_size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mem_block", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_slice_free1" g_slice_free1 :: 
    Word64 ->                               -- block_size : TBasicType TUInt64
    Ptr () ->                               -- mem_block : TBasicType TVoid
    IO ()


sliceFree1 ::
    (MonadIO m) =>
    Word64 ->                               -- block_size
    Ptr () ->                               -- mem_block
    m ()
sliceFree1 block_size mem_block = liftIO $ do
    g_slice_free1 block_size mem_block
    return ()


-- function g_shell_unquote
-- Args : [Arg {argName = "quoted_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "quoted_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_shell_unquote" g_shell_unquote :: 
    CString ->                              -- quoted_string : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString


shellUnquote ::
    (MonadIO m) =>
    T.Text ->                               -- quoted_string
    m T.Text
shellUnquote quoted_string = liftIO $ do
    quoted_string' <- textToCString quoted_string
    onException (do
        result <- propagateGError $ g_shell_unquote quoted_string'
        checkUnexpectedReturnNULL "g_shell_unquote" result
        result' <- cstringToText result
        freeMem result
        freeMem quoted_string'
        return result'
     ) (do
        freeMem quoted_string'
     )


-- function g_shell_quote
-- Args : [Arg {argName = "unquoted_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "unquoted_string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_shell_quote" g_shell_quote :: 
    CString ->                              -- unquoted_string : TBasicType TUTF8
    IO CString


shellQuote ::
    (MonadIO m) =>
    T.Text ->                               -- unquoted_string
    m T.Text
shellQuote unquoted_string = liftIO $ do
    unquoted_string' <- textToCString unquoted_string
    result <- g_shell_quote unquoted_string'
    checkUnexpectedReturnNULL "g_shell_quote" result
    result' <- cstringToText result
    freeMem result
    freeMem unquoted_string'
    return result'


-- function g_shell_parse_argv
-- Args : [Arg {argName = "command_line", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "argcp", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "argvp", argType = TCArray True (-1) 1 (TBasicType TUTF8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "command_line", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_shell_parse_argv" g_shell_parse_argv :: 
    CString ->                              -- command_line : TBasicType TUTF8
    Ptr Int32 ->                            -- argcp : TBasicType TInt32
    Ptr (Ptr CString) ->                    -- argvp : TCArray True (-1) 1 (TBasicType TUTF8)
    Ptr (Ptr GError) ->                     -- error
    IO CInt


shellParseArgv ::
    (MonadIO m) =>
    T.Text ->                               -- command_line
    m (Int32,[T.Text])
shellParseArgv command_line = liftIO $ do
    command_line' <- textToCString command_line
    argcp <- allocMem :: IO (Ptr Int32)
    argvp <- allocMem :: IO (Ptr (Ptr CString))
    onException (do
        _ <- propagateGError $ g_shell_parse_argv command_line' argcp argvp
        argcp' <- peek argcp
        argvp' <- peek argvp
        argvp'' <- unpackZeroTerminatedUTF8CArray argvp'
        mapZeroTerminatedCArray freeMem argvp'
        freeMem argvp'
        freeMem command_line'
        freeMem argcp
        freeMem argvp
        return (argcp', argvp'')
     ) (do
        freeMem command_line'
        freeMem argcp
        freeMem argvp
     )


-- function g_shell_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_shell_error_quark" g_shell_error_quark :: 
    IO Word32


shellErrorQuark ::
    (MonadIO m) =>
    m Word32
shellErrorQuark  = liftIO $ do
    result <- g_shell_error_quark
    return result


-- function g_setenv
-- Args : [Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "overwrite", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "overwrite", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_setenv" g_setenv :: 
    CString ->                              -- variable : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    CInt ->                                 -- overwrite : TBasicType TBoolean
    IO CInt


setenv ::
    (MonadIO m) =>
    T.Text ->                               -- variable
    T.Text ->                               -- value
    Bool ->                                 -- overwrite
    m Bool
setenv variable value overwrite = liftIO $ do
    variable' <- textToCString variable
    value' <- textToCString value
    let overwrite' = (fromIntegral . fromEnum) overwrite
    result <- g_setenv variable' value' overwrite'
    let result' = (/= 0) result
    freeMem variable'
    freeMem value'
    return result'


-- function g_set_prgname
-- Args : [Arg {argName = "prgname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "prgname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_set_prgname" g_set_prgname :: 
    CString ->                              -- prgname : TBasicType TUTF8
    IO ()


setPrgname ::
    (MonadIO m) =>
    T.Text ->                               -- prgname
    m ()
setPrgname prgname = liftIO $ do
    prgname' <- textToCString prgname
    g_set_prgname prgname'
    freeMem prgname'
    return ()


-- function g_set_error_literal
-- Args : [Arg {argName = "err", argType = TError, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "domain", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "code", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "message", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "err", argType = TError, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "domain", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "code", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "message", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_set_error_literal" g_set_error_literal :: 
    Ptr GError ->                           -- err : TError
    Word32 ->                               -- domain : TBasicType TUInt32
    Int32 ->                                -- code : TBasicType TInt32
    CString ->                              -- message : TBasicType TUTF8
    IO ()


setErrorLiteral ::
    (MonadIO m) =>
    Maybe (GError) ->                       -- err
    Word32 ->                               -- domain
    Int32 ->                                -- code
    T.Text ->                               -- message
    m ()
setErrorLiteral err domain code message = liftIO $ do
    maybeErr <- case err of
        Nothing -> return nullPtr
        Just jErr -> do
            let jErr' = unsafeManagedPtrGetPtr jErr
            return jErr'
    message' <- textToCString message
    g_set_error_literal maybeErr domain code message'
    whenJust err touchManagedPtr
    freeMem message'
    return ()


-- function g_set_application_name
-- Args : [Arg {argName = "application_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "application_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_set_application_name" g_set_application_name :: 
    CString ->                              -- application_name : TBasicType TUTF8
    IO ()


setApplicationName ::
    (MonadIO m) =>
    T.Text ->                               -- application_name
    m ()
setApplicationName application_name = liftIO $ do
    application_name' <- textToCString application_name
    g_set_application_name application_name'
    freeMem application_name'
    return ()


-- function g_sequence_swap
-- Args : [Arg {argName = "a", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "b", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "a", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "b", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_sequence_swap" g_sequence_swap :: 
    Ptr SequenceIter ->                     -- a : TInterface "GLib" "SequenceIter"
    Ptr SequenceIter ->                     -- b : TInterface "GLib" "SequenceIter"
    IO ()


sequenceSwap ::
    (MonadIO m) =>
    SequenceIter ->                         -- a
    SequenceIter ->                         -- b
    m ()
sequenceSwap a b = liftIO $ do
    let a' = unsafeManagedPtrGetPtr a
    let b' = unsafeManagedPtrGetPtr b
    g_sequence_swap a' b'
    touchManagedPtr a
    touchManagedPtr b
    return ()


-- function g_sequence_set
-- Args : [Arg {argName = "iter", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "iter", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_sequence_set" g_sequence_set :: 
    Ptr SequenceIter ->                     -- iter : TInterface "GLib" "SequenceIter"
    Ptr () ->                               -- data : TBasicType TVoid
    IO ()


sequenceSet ::
    (MonadIO m) =>
    SequenceIter ->                         -- iter
    Ptr () ->                               -- data
    m ()
sequenceSet iter data_ = liftIO $ do
    let iter' = unsafeManagedPtrGetPtr iter
    g_sequence_set iter' data_
    touchManagedPtr iter
    return ()


-- function g_sequence_remove_range
-- Args : [Arg {argName = "begin", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "begin", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_sequence_remove_range" g_sequence_remove_range :: 
    Ptr SequenceIter ->                     -- begin : TInterface "GLib" "SequenceIter"
    Ptr SequenceIter ->                     -- end : TInterface "GLib" "SequenceIter"
    IO ()


sequenceRemoveRange ::
    (MonadIO m) =>
    SequenceIter ->                         -- begin
    SequenceIter ->                         -- end
    m ()
sequenceRemoveRange begin end = liftIO $ do
    let begin' = unsafeManagedPtrGetPtr begin
    let end' = unsafeManagedPtrGetPtr end
    g_sequence_remove_range begin' end'
    touchManagedPtr begin
    touchManagedPtr end
    return ()


-- function g_sequence_remove
-- Args : [Arg {argName = "iter", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "iter", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_sequence_remove" g_sequence_remove :: 
    Ptr SequenceIter ->                     -- iter : TInterface "GLib" "SequenceIter"
    IO ()


sequenceRemove ::
    (MonadIO m) =>
    SequenceIter ->                         -- iter
    m ()
sequenceRemove iter = liftIO $ do
    let iter' = unsafeManagedPtrGetPtr iter
    g_sequence_remove iter'
    touchManagedPtr iter
    return ()


-- function g_sequence_move_range
-- Args : [Arg {argName = "dest", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "begin", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dest", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "begin", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_sequence_move_range" g_sequence_move_range :: 
    Ptr SequenceIter ->                     -- dest : TInterface "GLib" "SequenceIter"
    Ptr SequenceIter ->                     -- begin : TInterface "GLib" "SequenceIter"
    Ptr SequenceIter ->                     -- end : TInterface "GLib" "SequenceIter"
    IO ()


sequenceMoveRange ::
    (MonadIO m) =>
    SequenceIter ->                         -- dest
    SequenceIter ->                         -- begin
    SequenceIter ->                         -- end
    m ()
sequenceMoveRange dest begin end = liftIO $ do
    let dest' = unsafeManagedPtrGetPtr dest
    let begin' = unsafeManagedPtrGetPtr begin
    let end' = unsafeManagedPtrGetPtr end
    g_sequence_move_range dest' begin' end'
    touchManagedPtr dest
    touchManagedPtr begin
    touchManagedPtr end
    return ()


-- function g_sequence_move
-- Args : [Arg {argName = "src", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "src", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dest", argType = TInterface "GLib" "SequenceIter", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_sequence_move" g_sequence_move :: 
    Ptr SequenceIter ->                     -- src : TInterface "GLib" "SequenceIter"
    Ptr SequenceIter ->                     -- dest : TInterface "GLib" "SequenceIter"
    IO ()


sequenceMove ::
    (MonadIO m) =>
    SequenceIter ->                         -- src
    SequenceIter ->                         -- dest
    m ()
sequenceMove src dest = liftIO $ do
    let src' = unsafeManagedPtrGetPtr src
    let dest' = unsafeManagedPtrGetPtr dest
    g_sequence_move src' dest'
    touchManagedPtr src
    touchManagedPtr dest
    return ()


-- function g_rmdir
-- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_rmdir" g_rmdir :: 
    CString ->                              -- filename : TBasicType TUTF8
    IO Int32


rmdir ::
    (MonadIO m) =>
    T.Text ->                               -- filename
    m Int32
rmdir filename = liftIO $ do
    filename' <- textToCString filename
    result <- g_rmdir filename'
    freeMem filename'
    return result


-- function g_return_if_fail_warning
-- Args : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pretty_function", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expression", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pretty_function", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expression", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_return_if_fail_warning" g_return_if_fail_warning :: 
    CString ->                              -- log_domain : TBasicType TUTF8
    CString ->                              -- pretty_function : TBasicType TUTF8
    CString ->                              -- expression : TBasicType TUTF8
    IO ()


returnIfFailWarning ::
    (MonadIO m) =>
    T.Text ->                               -- log_domain
    T.Text ->                               -- pretty_function
    T.Text ->                               -- expression
    m ()
returnIfFailWarning log_domain pretty_function expression = liftIO $ do
    log_domain' <- textToCString log_domain
    pretty_function' <- textToCString pretty_function
    expression' <- textToCString expression
    g_return_if_fail_warning log_domain' pretty_function' expression'
    freeMem log_domain'
    freeMem pretty_function'
    freeMem expression'
    return ()


-- function g_reload_user_special_dirs_cache
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_reload_user_special_dirs_cache" g_reload_user_special_dirs_cache :: 
    IO ()


reloadUserSpecialDirsCache ::
    (MonadIO m) =>
    m ()
reloadUserSpecialDirsCache  = liftIO $ do
    g_reload_user_special_dirs_cache
    return ()


-- function g_regex_split_simple
-- Args : [Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "compile_options", argType = TInterface "GLib" "RegexCompileFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "match_options", argType = TInterface "GLib" "RegexMatchFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "compile_options", argType = TInterface "GLib" "RegexCompileFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "match_options", argType = TInterface "GLib" "RegexMatchFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_regex_split_simple" g_regex_split_simple :: 
    CString ->                              -- pattern : TBasicType TUTF8
    CString ->                              -- string : TBasicType TUTF8
    CUInt ->                                -- compile_options : TInterface "GLib" "RegexCompileFlags"
    CUInt ->                                -- match_options : TInterface "GLib" "RegexMatchFlags"
    IO (Ptr CString)


regexSplitSimple ::
    (MonadIO m) =>
    T.Text ->                               -- pattern
    T.Text ->                               -- string
    [RegexCompileFlags] ->                  -- compile_options
    [RegexMatchFlags] ->                    -- match_options
    m [T.Text]
regexSplitSimple pattern string compile_options match_options = liftIO $ do
    pattern' <- textToCString pattern
    string' <- textToCString string
    let compile_options' = gflagsToWord compile_options
    let match_options' = gflagsToWord match_options
    result <- g_regex_split_simple pattern' string' compile_options' match_options'
    checkUnexpectedReturnNULL "g_regex_split_simple" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    freeMem pattern'
    freeMem string'
    return result'


-- function g_regex_match_simple
-- Args : [Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "compile_options", argType = TInterface "GLib" "RegexCompileFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "match_options", argType = TInterface "GLib" "RegexMatchFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "compile_options", argType = TInterface "GLib" "RegexCompileFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "match_options", argType = TInterface "GLib" "RegexMatchFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_regex_match_simple" g_regex_match_simple :: 
    CString ->                              -- pattern : TBasicType TUTF8
    CString ->                              -- string : TBasicType TUTF8
    CUInt ->                                -- compile_options : TInterface "GLib" "RegexCompileFlags"
    CUInt ->                                -- match_options : TInterface "GLib" "RegexMatchFlags"
    IO CInt


regexMatchSimple ::
    (MonadIO m) =>
    T.Text ->                               -- pattern
    T.Text ->                               -- string
    [RegexCompileFlags] ->                  -- compile_options
    [RegexMatchFlags] ->                    -- match_options
    m Bool
regexMatchSimple pattern string compile_options match_options = liftIO $ do
    pattern' <- textToCString pattern
    string' <- textToCString string
    let compile_options' = gflagsToWord compile_options
    let match_options' = gflagsToWord match_options
    result <- g_regex_match_simple pattern' string' compile_options' match_options'
    let result' = (/= 0) result
    freeMem pattern'
    freeMem string'
    return result'


-- function g_regex_escape_string
-- Args : [Arg {argName = "string", argType = TCArray False (-1) 1 (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "string", argType = TCArray False (-1) 1 (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_regex_escape_string" g_regex_escape_string :: 
    Ptr CString ->                          -- string : TCArray False (-1) 1 (TBasicType TUTF8)
    Int32 ->                                -- length : TBasicType TInt32
    IO CString


regexEscapeString ::
    (MonadIO m) =>
    [T.Text] ->                             -- string
    m T.Text
regexEscapeString string = liftIO $ do
    let length_ = fromIntegral $ length string
    string' <- packUTF8CArray string
    result <- g_regex_escape_string string' length_
    checkUnexpectedReturnNULL "g_regex_escape_string" result
    result' <- cstringToText result
    freeMem result
    (mapCArrayWithLength length_) freeMem string'
    freeMem string'
    return result'


-- function g_regex_escape_nul
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_regex_escape_nul" g_regex_escape_nul :: 
    CString ->                              -- string : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    IO CString


regexEscapeNul ::
    (MonadIO m) =>
    T.Text ->                               -- string
    Int32 ->                                -- length
    m T.Text
regexEscapeNul string length_ = liftIO $ do
    string' <- textToCString string
    result <- g_regex_escape_nul string' length_
    checkUnexpectedReturnNULL "g_regex_escape_nul" result
    result' <- cstringToText result
    freeMem result
    freeMem string'
    return result'


-- function g_regex_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_regex_error_quark" g_regex_error_quark :: 
    IO Word32


regexErrorQuark ::
    (MonadIO m) =>
    m Word32
regexErrorQuark  = liftIO $ do
    result <- g_regex_error_quark
    return result


-- function g_regex_check_replacement
-- Args : [Arg {argName = "replacement", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "has_references", argType = TBasicType TBoolean, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "replacement", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_regex_check_replacement" g_regex_check_replacement :: 
    CString ->                              -- replacement : TBasicType TUTF8
    Ptr CInt ->                             -- has_references : TBasicType TBoolean
    Ptr (Ptr GError) ->                     -- error
    IO CInt


regexCheckReplacement ::
    (MonadIO m) =>
    T.Text ->                               -- replacement
    m (Bool)
regexCheckReplacement replacement = liftIO $ do
    replacement' <- textToCString replacement
    has_references <- allocMem :: IO (Ptr CInt)
    onException (do
        _ <- propagateGError $ g_regex_check_replacement replacement' has_references
        has_references' <- peek has_references
        let has_references'' = (/= 0) has_references'
        freeMem replacement'
        freeMem has_references
        return has_references''
     ) (do
        freeMem replacement'
        freeMem has_references
     )


-- function g_random_set_seed
-- Args : [Arg {argName = "seed", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "seed", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_random_set_seed" g_random_set_seed :: 
    Word32 ->                               -- seed : TBasicType TUInt32
    IO ()


randomSetSeed ::
    (MonadIO m) =>
    Word32 ->                               -- seed
    m ()
randomSetSeed seed = liftIO $ do
    g_random_set_seed seed
    return ()


-- function g_random_int_range
-- Args : [Arg {argName = "begin", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "begin", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_random_int_range" g_random_int_range :: 
    Int32 ->                                -- begin : TBasicType TInt32
    Int32 ->                                -- end : TBasicType TInt32
    IO Int32


randomIntRange ::
    (MonadIO m) =>
    Int32 ->                                -- begin
    Int32 ->                                -- end
    m Int32
randomIntRange begin end = liftIO $ do
    result <- g_random_int_range begin end
    return result


-- function g_random_int
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_random_int" g_random_int :: 
    IO Word32


randomInt ::
    (MonadIO m) =>
    m Word32
randomInt  = liftIO $ do
    result <- g_random_int
    return result


-- function g_random_double_range
-- Args : [Arg {argName = "begin", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "begin", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "g_random_double_range" g_random_double_range :: 
    CDouble ->                              -- begin : TBasicType TDouble
    CDouble ->                              -- end : TBasicType TDouble
    IO CDouble


randomDoubleRange ::
    (MonadIO m) =>
    Double ->                               -- begin
    Double ->                               -- end
    m Double
randomDoubleRange begin end = liftIO $ do
    let begin' = realToFrac begin
    let end' = realToFrac end
    result <- g_random_double_range begin' end'
    let result' = realToFrac result
    return result'


-- function g_random_double
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "g_random_double" g_random_double :: 
    IO CDouble


randomDouble ::
    (MonadIO m) =>
    m Double
randomDouble  = liftIO $ do
    result <- g_random_double
    let result' = realToFrac result
    return result'


-- function g_quark_try_string
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_quark_try_string" g_quark_try_string :: 
    CString ->                              -- string : TBasicType TUTF8
    IO Word32


quarkTryString ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- string
    m Word32
quarkTryString string = liftIO $ do
    maybeString <- case string of
        Nothing -> return nullPtr
        Just jString -> do
            jString' <- textToCString jString
            return jString'
    result <- g_quark_try_string maybeString
    freeMem maybeString
    return result


-- function g_quark_to_string
-- Args : [Arg {argName = "quark", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "quark", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_quark_to_string" g_quark_to_string :: 
    Word32 ->                               -- quark : TBasicType TUInt32
    IO CString


quarkToString ::
    (MonadIO m) =>
    Word32 ->                               -- quark
    m T.Text
quarkToString quark = liftIO $ do
    result <- g_quark_to_string quark
    checkUnexpectedReturnNULL "g_quark_to_string" result
    result' <- cstringToText result
    return result'


-- function g_quark_from_string
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_quark_from_string" g_quark_from_string :: 
    CString ->                              -- string : TBasicType TUTF8
    IO Word32


quarkFromString ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- string
    m Word32
quarkFromString string = liftIO $ do
    maybeString <- case string of
        Nothing -> return nullPtr
        Just jString -> do
            jString' <- textToCString jString
            return jString'
    result <- g_quark_from_string maybeString
    freeMem maybeString
    return result


-- function g_quark_from_static_string
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_quark_from_static_string" g_quark_from_static_string :: 
    CString ->                              -- string : TBasicType TUTF8
    IO Word32


quarkFromStaticString ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- string
    m Word32
quarkFromStaticString string = liftIO $ do
    maybeString <- case string of
        Nothing -> return nullPtr
        Just jString -> do
            jString' <- textToCString jString
            return jString'
    result <- g_quark_from_static_string maybeString
    freeMem maybeString
    return result


-- function g_propagate_error
-- Args : [Arg {argName = "dest", argType = TError, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TError, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dest", argType = TError, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "src", argType = TError, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_propagate_error" g_propagate_error :: 
    Ptr GError ->                           -- dest : TError
    Ptr GError ->                           -- src : TError
    IO ()


propagateError ::
    (MonadIO m) =>
    GError ->                               -- dest
    GError ->                               -- src
    m ()
propagateError dest src = liftIO $ do
    let dest' = unsafeManagedPtrGetPtr dest
    let src' = unsafeManagedPtrGetPtr src
    g_propagate_error dest' src'
    touchManagedPtr dest
    touchManagedPtr src
    return ()


-- function g_poll
-- Args : [Arg {argName = "fds", argType = TInterface "GLib" "PollFD", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nfds", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "timeout", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "fds", argType = TInterface "GLib" "PollFD", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nfds", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "timeout", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_poll" g_poll :: 
    Ptr PollFD ->                           -- fds : TInterface "GLib" "PollFD"
    Word32 ->                               -- nfds : TBasicType TUInt32
    Int32 ->                                -- timeout : TBasicType TInt32
    IO Int32


poll ::
    (MonadIO m) =>
    PollFD ->                               -- fds
    Word32 ->                               -- nfds
    Int32 ->                                -- timeout
    m Int32
poll fds nfds timeout = liftIO $ do
    let fds' = unsafeManagedPtrGetPtr fds
    result <- g_poll fds' nfds timeout
    touchManagedPtr fds
    return result


-- function g_pointer_bit_unlock
-- Args : [Arg {argName = "address", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "address", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_pointer_bit_unlock" g_pointer_bit_unlock :: 
    Ptr () ->                               -- address : TBasicType TVoid
    Int32 ->                                -- lock_bit : TBasicType TInt32
    IO ()


pointerBitUnlock ::
    (MonadIO m) =>
    Ptr () ->                               -- address
    Int32 ->                                -- lock_bit
    m ()
pointerBitUnlock address lock_bit = liftIO $ do
    g_pointer_bit_unlock address lock_bit
    return ()


-- function g_pointer_bit_trylock
-- Args : [Arg {argName = "address", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "address", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_pointer_bit_trylock" g_pointer_bit_trylock :: 
    Ptr () ->                               -- address : TBasicType TVoid
    Int32 ->                                -- lock_bit : TBasicType TInt32
    IO CInt


pointerBitTrylock ::
    (MonadIO m) =>
    Ptr () ->                               -- address
    Int32 ->                                -- lock_bit
    m Bool
pointerBitTrylock address lock_bit = liftIO $ do
    result <- g_pointer_bit_trylock address lock_bit
    let result' = (/= 0) result
    return result'


-- function g_pointer_bit_lock
-- Args : [Arg {argName = "address", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "address", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_pointer_bit_lock" g_pointer_bit_lock :: 
    Ptr () ->                               -- address : TBasicType TVoid
    Int32 ->                                -- lock_bit : TBasicType TInt32
    IO ()


pointerBitLock ::
    (MonadIO m) =>
    Ptr () ->                               -- address
    Int32 ->                                -- lock_bit
    m ()
pointerBitLock address lock_bit = liftIO $ do
    g_pointer_bit_lock address lock_bit
    return ()


-- function g_pattern_match_string
-- Args : [Arg {argName = "pspec", argType = TInterface "GLib" "PatternSpec", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pspec", argType = TInterface "GLib" "PatternSpec", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_pattern_match_string" g_pattern_match_string :: 
    Ptr PatternSpec ->                      -- pspec : TInterface "GLib" "PatternSpec"
    CString ->                              -- string : TBasicType TUTF8
    IO CInt


patternMatchString ::
    (MonadIO m) =>
    PatternSpec ->                          -- pspec
    T.Text ->                               -- string
    m Bool
patternMatchString pspec string = liftIO $ do
    let pspec' = unsafeManagedPtrGetPtr pspec
    string' <- textToCString string
    result <- g_pattern_match_string pspec' string'
    let result' = (/= 0) result
    touchManagedPtr pspec
    freeMem string'
    return result'


-- function g_pattern_match_simple
-- Args : [Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pattern", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_pattern_match_simple" g_pattern_match_simple :: 
    CString ->                              -- pattern : TBasicType TUTF8
    CString ->                              -- string : TBasicType TUTF8
    IO CInt


patternMatchSimple ::
    (MonadIO m) =>
    T.Text ->                               -- pattern
    T.Text ->                               -- string
    m Bool
patternMatchSimple pattern string = liftIO $ do
    pattern' <- textToCString pattern
    string' <- textToCString string
    result <- g_pattern_match_simple pattern' string'
    let result' = (/= 0) result
    freeMem pattern'
    freeMem string'
    return result'


-- function g_pattern_match
-- Args : [Arg {argName = "pspec", argType = TInterface "GLib" "PatternSpec", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string_length", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string_reversed", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pspec", argType = TInterface "GLib" "PatternSpec", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string_length", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "string_reversed", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_pattern_match" g_pattern_match :: 
    Ptr PatternSpec ->                      -- pspec : TInterface "GLib" "PatternSpec"
    Word32 ->                               -- string_length : TBasicType TUInt32
    CString ->                              -- string : TBasicType TUTF8
    CString ->                              -- string_reversed : TBasicType TUTF8
    IO CInt


patternMatch ::
    (MonadIO m) =>
    PatternSpec ->                          -- pspec
    Word32 ->                               -- string_length
    T.Text ->                               -- string
    Maybe (T.Text) ->                       -- string_reversed
    m Bool
patternMatch pspec string_length string string_reversed = liftIO $ do
    let pspec' = unsafeManagedPtrGetPtr pspec
    string' <- textToCString string
    maybeString_reversed <- case string_reversed of
        Nothing -> return nullPtr
        Just jString_reversed -> do
            jString_reversed' <- textToCString jString_reversed
            return jString_reversed'
    result <- g_pattern_match pspec' string_length string' maybeString_reversed
    let result' = (/= 0) result
    touchManagedPtr pspec
    freeMem string'
    freeMem maybeString_reversed
    return result'


-- function g_path_skip_root
-- Args : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_path_skip_root" g_path_skip_root :: 
    CString ->                              -- file_name : TBasicType TUTF8
    IO CString


pathSkipRoot ::
    (MonadIO m) =>
    T.Text ->                               -- file_name
    m T.Text
pathSkipRoot file_name = liftIO $ do
    file_name' <- textToCString file_name
    result <- g_path_skip_root file_name'
    checkUnexpectedReturnNULL "g_path_skip_root" result
    result' <- cstringToText result
    freeMem file_name'
    return result'


-- function g_path_is_absolute
-- Args : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_path_is_absolute" g_path_is_absolute :: 
    CString ->                              -- file_name : TBasicType TUTF8
    IO CInt


pathIsAbsolute ::
    (MonadIO m) =>
    T.Text ->                               -- file_name
    m Bool
pathIsAbsolute file_name = liftIO $ do
    file_name' <- textToCString file_name
    result <- g_path_is_absolute file_name'
    let result' = (/= 0) result
    freeMem file_name'
    return result'


-- function g_path_get_dirname
-- Args : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_path_get_dirname" g_path_get_dirname :: 
    CString ->                              -- file_name : TBasicType TUTF8
    IO CString


pathGetDirname ::
    (MonadIO m) =>
    T.Text ->                               -- file_name
    m T.Text
pathGetDirname file_name = liftIO $ do
    file_name' <- textToCString file_name
    result <- g_path_get_dirname file_name'
    checkUnexpectedReturnNULL "g_path_get_dirname" result
    result' <- cstringToText result
    freeMem result
    freeMem file_name'
    return result'


-- function g_path_get_basename
-- Args : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_path_get_basename" g_path_get_basename :: 
    CString ->                              -- file_name : TBasicType TUTF8
    IO CString


pathGetBasename ::
    (MonadIO m) =>
    T.Text ->                               -- file_name
    m T.Text
pathGetBasename file_name = liftIO $ do
    file_name' <- textToCString file_name
    result <- g_path_get_basename file_name'
    checkUnexpectedReturnNULL "g_path_get_basename" result
    result' <- cstringToText result
    freeMem result
    freeMem file_name'
    return result'


-- function g_parse_debug_string
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "keys", argType = TCArray False (-1) 2 (TInterface "GLib" "DebugKey"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nkeys", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "nkeys", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "keys", argType = TCArray False (-1) 2 (TInterface "GLib" "DebugKey"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_parse_debug_string" g_parse_debug_string :: 
    CString ->                              -- string : TBasicType TUTF8
    Ptr DebugKey ->                         -- keys : TCArray False (-1) 2 (TInterface "GLib" "DebugKey")
    Word32 ->                               -- nkeys : TBasicType TUInt32
    IO Word32


parseDebugString ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- string
    [DebugKey] ->                           -- keys
    m Word32
parseDebugString string keys = liftIO $ do
    let nkeys = fromIntegral $ length keys
    maybeString <- case string of
        Nothing -> return nullPtr
        Just jString -> do
            jString' <- textToCString jString
            return jString'
    let keys' = map unsafeManagedPtrGetPtr keys
    keys'' <- packBlockArray 16 keys'
    result <- g_parse_debug_string maybeString keys'' nkeys
    mapM_ touchManagedPtr keys
    freeMem maybeString
    freeMem keys''
    return result


-- function g_option_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_option_error_quark" g_option_error_quark :: 
    IO Word32


optionErrorQuark ::
    (MonadIO m) =>
    m Word32
optionErrorQuark  = liftIO $ do
    result <- g_option_error_quark
    return result


-- function g_once_init_leave
-- Args : [Arg {argName = "location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "result", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_once_init_leave" g_once_init_leave :: 
    Ptr () ->                               -- location : TBasicType TVoid
    Word64 ->                               -- result : TBasicType TUInt64
    IO ()


onceInitLeave ::
    (MonadIO m) =>
    Ptr () ->                               -- location
    Word64 ->                               -- result
    m ()
onceInitLeave location result_ = liftIO $ do
    g_once_init_leave location result_
    return ()


-- function g_once_init_enter
-- Args : [Arg {argName = "location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_once_init_enter" g_once_init_enter :: 
    Ptr () ->                               -- location : TBasicType TVoid
    IO CInt


onceInitEnter ::
    (MonadIO m) =>
    Ptr () ->                               -- location
    m Bool
onceInitEnter location = liftIO $ do
    result <- g_once_init_enter location
    let result' = (/= 0) result
    return result'


-- function g_on_error_stack_trace
-- Args : [Arg {argName = "prg_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "prg_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_on_error_stack_trace" g_on_error_stack_trace :: 
    CString ->                              -- prg_name : TBasicType TUTF8
    IO ()


onErrorStackTrace ::
    (MonadIO m) =>
    T.Text ->                               -- prg_name
    m ()
onErrorStackTrace prg_name = liftIO $ do
    prg_name' <- textToCString prg_name
    g_on_error_stack_trace prg_name'
    freeMem prg_name'
    return ()


-- function g_on_error_query
-- Args : [Arg {argName = "prg_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "prg_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_on_error_query" g_on_error_query :: 
    CString ->                              -- prg_name : TBasicType TUTF8
    IO ()


onErrorQuery ::
    (MonadIO m) =>
    T.Text ->                               -- prg_name
    m ()
onErrorQuery prg_name = liftIO $ do
    prg_name' <- textToCString prg_name
    g_on_error_query prg_name'
    freeMem prg_name'
    return ()


-- function g_nullify_pointer
-- Args : [Arg {argName = "nullify_location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "nullify_location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_nullify_pointer" g_nullify_pointer :: 
    Ptr () ->                               -- nullify_location : TBasicType TVoid
    IO ()


nullifyPointer ::
    (MonadIO m) =>
    Ptr () ->                               -- nullify_location
    m ()
nullifyPointer nullify_location = liftIO $ do
    g_nullify_pointer nullify_location
    return ()


-- function g_mkstemp_full
-- Args : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_mkstemp_full" g_mkstemp_full :: 
    CString ->                              -- tmpl : TBasicType TFileName
    Int32 ->                                -- flags : TBasicType TInt32
    Int32 ->                                -- mode : TBasicType TInt32
    IO Int32


mkstempFull ::
    (MonadIO m) =>
    [Char] ->                               -- tmpl
    Int32 ->                                -- flags
    Int32 ->                                -- mode
    m Int32
mkstempFull tmpl flags mode = liftIO $ do
    tmpl' <- stringToCString tmpl
    result <- g_mkstemp_full tmpl' flags mode
    freeMem tmpl'
    return result


-- function g_mkstemp
-- Args : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_mkstemp" g_mkstemp :: 
    CString ->                              -- tmpl : TBasicType TFileName
    IO Int32


mkstemp ::
    (MonadIO m) =>
    [Char] ->                               -- tmpl
    m Int32
mkstemp tmpl = liftIO $ do
    tmpl' <- stringToCString tmpl
    result <- g_mkstemp tmpl'
    freeMem tmpl'
    return result


-- function g_mkdtemp_full
-- Args : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_mkdtemp_full" g_mkdtemp_full :: 
    CString ->                              -- tmpl : TBasicType TFileName
    Int32 ->                                -- mode : TBasicType TInt32
    IO CString


mkdtempFull ::
    (MonadIO m) =>
    [Char] ->                               -- tmpl
    Int32 ->                                -- mode
    m T.Text
mkdtempFull tmpl mode = liftIO $ do
    tmpl' <- stringToCString tmpl
    result <- g_mkdtemp_full tmpl' mode
    checkUnexpectedReturnNULL "g_mkdtemp_full" result
    result' <- cstringToText result
    freeMem result
    freeMem tmpl'
    return result'


-- function g_mkdtemp
-- Args : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_mkdtemp" g_mkdtemp :: 
    CString ->                              -- tmpl : TBasicType TFileName
    IO CString


mkdtemp ::
    (MonadIO m) =>
    [Char] ->                               -- tmpl
    m T.Text
mkdtemp tmpl = liftIO $ do
    tmpl' <- stringToCString tmpl
    result <- g_mkdtemp tmpl'
    checkUnexpectedReturnNULL "g_mkdtemp" result
    result' <- cstringToText result
    freeMem result
    freeMem tmpl'
    return result'


-- function g_mkdir_with_parents
-- Args : [Arg {argName = "pathname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pathname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_mkdir_with_parents" g_mkdir_with_parents :: 
    CString ->                              -- pathname : TBasicType TUTF8
    Int32 ->                                -- mode : TBasicType TInt32
    IO Int32


mkdirWithParents ::
    (MonadIO m) =>
    T.Text ->                               -- pathname
    Int32 ->                                -- mode
    m Int32
mkdirWithParents pathname mode = liftIO $ do
    pathname' <- textToCString pathname
    result <- g_mkdir_with_parents pathname' mode
    freeMem pathname'
    return result


-- function g_mem_set_vtable
-- Args : [Arg {argName = "vtable", argType = TInterface "GLib" "MemVTable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "vtable", argType = TInterface "GLib" "MemVTable", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_set_vtable" g_mem_set_vtable :: 
    Ptr MemVTable ->                        -- vtable : TInterface "GLib" "MemVTable"
    IO ()

{-# DEPRECATED memSetVtable ["(Since version 2.46)","Use other memory profiling tools instead"]#-}
memSetVtable ::
    (MonadIO m) =>
    MemVTable ->                            -- vtable
    m ()
memSetVtable vtable = liftIO $ do
    let vtable' = unsafeManagedPtrGetPtr vtable
    g_mem_set_vtable vtable'
    touchManagedPtr vtable
    return ()


-- function g_mem_profile
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_profile" g_mem_profile :: 
    IO ()

{-# DEPRECATED memProfile ["(Since version 2.46)","Use other memory profiling tools instead"]#-}
memProfile ::
    (MonadIO m) =>
    m ()
memProfile  = liftIO $ do
    g_mem_profile
    return ()


-- function g_mem_is_system_malloc
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_mem_is_system_malloc" g_mem_is_system_malloc :: 
    IO CInt

{-# DEPRECATED memIsSystemMalloc ["(Since version 2.46)","GLib always uses the system malloc, so this function always","returns %TRUE."]#-}
memIsSystemMalloc ::
    (MonadIO m) =>
    m Bool
memIsSystemMalloc  = liftIO $ do
    result <- g_mem_is_system_malloc
    let result' = (/= 0) result
    return result'


-- function g_markup_escape_text
-- Args : [Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_markup_escape_text" g_markup_escape_text :: 
    CString ->                              -- text : TBasicType TUTF8
    Int64 ->                                -- length : TBasicType TInt64
    IO CString


markupEscapeText ::
    (MonadIO m) =>
    T.Text ->                               -- text
    Int64 ->                                -- length
    m T.Text
markupEscapeText text length_ = liftIO $ do
    text' <- textToCString text
    result <- g_markup_escape_text text' length_
    checkUnexpectedReturnNULL "g_markup_escape_text" result
    result' <- cstringToText result
    freeMem result
    freeMem text'
    return result'


-- function g_markup_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_markup_error_quark" g_markup_error_quark :: 
    IO Word32


markupErrorQuark ::
    (MonadIO m) =>
    m Word32
markupErrorQuark  = liftIO $ do
    result <- g_markup_error_quark
    return result


-- function g_main_depth
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_main_depth" g_main_depth :: 
    IO Int32


mainDepth ::
    (MonadIO m) =>
    m Int32
mainDepth  = liftIO $ do
    result <- g_main_depth
    return result


-- function g_main_current_source
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "GLib" "Source"
-- throws : False
-- Skip return : False

foreign import ccall "g_main_current_source" g_main_current_source :: 
    IO (Ptr Source)


mainCurrentSource ::
    (MonadIO m) =>
    m Source
mainCurrentSource  = liftIO $ do
    result <- g_main_current_source
    checkUnexpectedReturnNULL "g_main_current_source" result
    result' <- (newBoxed Source) result
    return result'


-- function g_main_context_ref_thread_default
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "GLib" "MainContext"
-- throws : False
-- Skip return : False

foreign import ccall "g_main_context_ref_thread_default" g_main_context_ref_thread_default :: 
    IO (Ptr MainContext)


mainContextRefThreadDefault ::
    (MonadIO m) =>
    m MainContext
mainContextRefThreadDefault  = liftIO $ do
    result <- g_main_context_ref_thread_default
    checkUnexpectedReturnNULL "g_main_context_ref_thread_default" result
    result' <- (wrapBoxed MainContext) result
    return result'


-- function g_main_context_get_thread_default
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "GLib" "MainContext"
-- throws : False
-- Skip return : False

foreign import ccall "g_main_context_get_thread_default" g_main_context_get_thread_default :: 
    IO (Ptr MainContext)


mainContextGetThreadDefault ::
    (MonadIO m) =>
    m MainContext
mainContextGetThreadDefault  = liftIO $ do
    result <- g_main_context_get_thread_default
    checkUnexpectedReturnNULL "g_main_context_get_thread_default" result
    result' <- (newBoxed MainContext) result
    return result'


-- function g_main_context_default
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "GLib" "MainContext"
-- throws : False
-- Skip return : False

foreign import ccall "g_main_context_default" g_main_context_default :: 
    IO (Ptr MainContext)


mainContextDefault ::
    (MonadIO m) =>
    m MainContext
mainContextDefault  = liftIO $ do
    result <- g_main_context_default
    checkUnexpectedReturnNULL "g_main_context_default" result
    result' <- (newBoxed MainContext) result
    return result'


-- function g_log_set_handler_full
-- Args : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_levels", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_func", argType = TInterface "GLib" "LogFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_levels", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_func", argType = TInterface "GLib" "LogFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_log_set_handler_full" g_log_set_handler_full :: 
    CString ->                              -- log_domain : TBasicType TUTF8
    CUInt ->                                -- log_levels : TInterface "GLib" "LogLevelFlags"
    FunPtr LogFuncC ->                      -- log_func : TInterface "GLib" "LogFunc"
    Ptr () ->                               -- user_data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- destroy : TInterface "GLib" "DestroyNotify"
    IO Word32


logSetHandler ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- log_domain
    [LogLevelFlags] ->                      -- log_levels
    LogFunc ->                              -- log_func
    m Word32
logSetHandler log_domain log_levels log_func = liftIO $ do
    maybeLog_domain <- case log_domain of
        Nothing -> return nullPtr
        Just jLog_domain -> do
            jLog_domain' <- textToCString jLog_domain
            return jLog_domain'
    let log_levels' = gflagsToWord log_levels
    log_func' <- mkLogFunc (logFuncWrapper Nothing log_func)
    let user_data = castFunPtrToPtr log_func'
    let destroy = safeFreeFunPtrPtr
    result <- g_log_set_handler_full maybeLog_domain log_levels' log_func' user_data destroy
    freeMem maybeLog_domain
    return result


-- function g_log_set_fatal_mask
-- Args : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fatal_mask", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fatal_mask", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "LogLevelFlags"
-- throws : False
-- Skip return : False

foreign import ccall "g_log_set_fatal_mask" g_log_set_fatal_mask :: 
    CString ->                              -- log_domain : TBasicType TUTF8
    CUInt ->                                -- fatal_mask : TInterface "GLib" "LogLevelFlags"
    IO CUInt


logSetFatalMask ::
    (MonadIO m) =>
    T.Text ->                               -- log_domain
    [LogLevelFlags] ->                      -- fatal_mask
    m [LogLevelFlags]
logSetFatalMask log_domain fatal_mask = liftIO $ do
    log_domain' <- textToCString log_domain
    let fatal_mask' = gflagsToWord fatal_mask
    result <- g_log_set_fatal_mask log_domain' fatal_mask'
    let result' = wordToGFlags result
    freeMem log_domain'
    return result'


-- function g_log_set_always_fatal
-- Args : [Arg {argName = "fatal_mask", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "fatal_mask", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "LogLevelFlags"
-- throws : False
-- Skip return : False

foreign import ccall "g_log_set_always_fatal" g_log_set_always_fatal :: 
    CUInt ->                                -- fatal_mask : TInterface "GLib" "LogLevelFlags"
    IO CUInt


logSetAlwaysFatal ::
    (MonadIO m) =>
    [LogLevelFlags] ->                      -- fatal_mask
    m [LogLevelFlags]
logSetAlwaysFatal fatal_mask = liftIO $ do
    let fatal_mask' = gflagsToWord fatal_mask
    result <- g_log_set_always_fatal fatal_mask'
    let result' = wordToGFlags result
    return result'


-- function g_log_remove_handler
-- Args : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "handler_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "handler_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_log_remove_handler" g_log_remove_handler :: 
    CString ->                              -- log_domain : TBasicType TUTF8
    Word32 ->                               -- handler_id : TBasicType TUInt32
    IO ()


logRemoveHandler ::
    (MonadIO m) =>
    T.Text ->                               -- log_domain
    Word32 ->                               -- handler_id
    m ()
logRemoveHandler log_domain handler_id = liftIO $ do
    log_domain' <- textToCString log_domain
    g_log_remove_handler log_domain' handler_id
    freeMem log_domain'
    return ()


-- function g_log_default_handler
-- Args : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_level", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "message", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "unused_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_level", argType = TInterface "GLib" "LogLevelFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "message", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "unused_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_log_default_handler" g_log_default_handler :: 
    CString ->                              -- log_domain : TBasicType TUTF8
    CUInt ->                                -- log_level : TInterface "GLib" "LogLevelFlags"
    CString ->                              -- message : TBasicType TUTF8
    Ptr () ->                               -- unused_data : TBasicType TVoid
    IO ()


logDefaultHandler ::
    (MonadIO m) =>
    T.Text ->                               -- log_domain
    [LogLevelFlags] ->                      -- log_level
    T.Text ->                               -- message
    Ptr () ->                               -- unused_data
    m ()
logDefaultHandler log_domain log_level message unused_data = liftIO $ do
    log_domain' <- textToCString log_domain
    let log_level' = gflagsToWord log_level
    message' <- textToCString message
    g_log_default_handler log_domain' log_level' message' unused_data
    freeMem log_domain'
    freeMem message'
    return ()


-- function g_locale_to_utf8
-- Args : [Arg {argName = "opsysstring", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "opsysstring", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_locale_to_utf8" g_locale_to_utf8 :: 
    CString ->                              -- opsysstring : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    Word64 ->                               -- bytes_read : TBasicType TUInt64
    Word64 ->                               -- bytes_written : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString


localeToUtf8 ::
    (MonadIO m) =>
    T.Text ->                               -- opsysstring
    Int64 ->                                -- len
    Word64 ->                               -- bytes_read
    Word64 ->                               -- bytes_written
    m T.Text
localeToUtf8 opsysstring len bytes_read bytes_written = liftIO $ do
    opsysstring' <- textToCString opsysstring
    onException (do
        result <- propagateGError $ g_locale_to_utf8 opsysstring' len bytes_read bytes_written
        checkUnexpectedReturnNULL "g_locale_to_utf8" result
        result' <- cstringToText result
        freeMem result
        freeMem opsysstring'
        return result'
     ) (do
        freeMem opsysstring'
     )


-- function g_locale_from_utf8
-- Args : [Arg {argName = "utf8string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "utf8string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_locale_from_utf8" g_locale_from_utf8 :: 
    CString ->                              -- utf8string : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    Word64 ->                               -- bytes_read : TBasicType TUInt64
    Word64 ->                               -- bytes_written : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString


localeFromUtf8 ::
    (MonadIO m) =>
    T.Text ->                               -- utf8string
    Int64 ->                                -- len
    Word64 ->                               -- bytes_read
    Word64 ->                               -- bytes_written
    m T.Text
localeFromUtf8 utf8string len bytes_read bytes_written = liftIO $ do
    utf8string' <- textToCString utf8string
    onException (do
        result <- propagateGError $ g_locale_from_utf8 utf8string' len bytes_read bytes_written
        checkUnexpectedReturnNULL "g_locale_from_utf8" result
        result' <- cstringToText result
        freeMem result
        freeMem utf8string'
        return result'
     ) (do
        freeMem utf8string'
     )


-- function g_listenv
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_listenv" g_listenv :: 
    IO (Ptr CString)


listenv ::
    (MonadIO m) =>
    m [T.Text]
listenv  = liftIO $ do
    result <- g_listenv
    checkUnexpectedReturnNULL "g_listenv" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    return result'


-- function g_key_file_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_key_file_error_quark" g_key_file_error_quark :: 
    IO Word32


keyFileErrorQuark ::
    (MonadIO m) =>
    m Word32
keyFileErrorQuark  = liftIO $ do
    result <- g_key_file_error_quark
    return result


-- function g_io_create_watch
-- Args : [Arg {argName = "channel", argType = TInterface "GLib" "IOChannel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "condition", argType = TInterface "GLib" "IOCondition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "channel", argType = TInterface "GLib" "IOChannel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "condition", argType = TInterface "GLib" "IOCondition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "Source"
-- throws : False
-- Skip return : False

foreign import ccall "g_io_create_watch" g_io_create_watch :: 
    Ptr IOChannel ->                        -- channel : TInterface "GLib" "IOChannel"
    CUInt ->                                -- condition : TInterface "GLib" "IOCondition"
    IO (Ptr Source)


ioCreateWatch ::
    (MonadIO m) =>
    IOChannel ->                            -- channel
    [IOCondition] ->                        -- condition
    m Source
ioCreateWatch channel condition = liftIO $ do
    let channel' = unsafeManagedPtrGetPtr channel
    let condition' = gflagsToWord condition
    result <- g_io_create_watch channel' condition'
    checkUnexpectedReturnNULL "g_io_create_watch" result
    result' <- (wrapBoxed Source) result
    touchManagedPtr channel
    return result'


-- function g_io_channel_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_io_channel_error_quark" g_io_channel_error_quark :: 
    IO Word32


ioChannelErrorQuark ::
    (MonadIO m) =>
    m Word32
ioChannelErrorQuark  = liftIO $ do
    result <- g_io_channel_error_quark
    return result


-- function g_io_channel_error_from_errno
-- Args : [Arg {argName = "en", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "en", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "IOChannelError"
-- throws : False
-- Skip return : False

foreign import ccall "g_io_channel_error_from_errno" g_io_channel_error_from_errno :: 
    Int32 ->                                -- en : TBasicType TInt32
    IO CUInt


ioChannelErrorFromErrno ::
    (MonadIO m) =>
    Int32 ->                                -- en
    m IOChannelError
ioChannelErrorFromErrno en = liftIO $ do
    result <- g_io_channel_error_from_errno en
    let result' = (toEnum . fromIntegral) result
    return result'


-- function g_io_add_watch_full
-- Args : [Arg {argName = "channel", argType = TInterface "GLib" "IOChannel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "condition", argType = TInterface "GLib" "IOCondition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TInterface "GLib" "IOFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 4, argDestroy = 5, transfer = TransferNothing},Arg {argName = "user_data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "notify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "channel", argType = TInterface "GLib" "IOChannel", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "condition", argType = TInterface "GLib" "IOCondition", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TInterface "GLib" "IOFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 4, argDestroy = 5, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_io_add_watch_full" g_io_add_watch_full :: 
    Ptr IOChannel ->                        -- channel : TInterface "GLib" "IOChannel"
    Int32 ->                                -- priority : TBasicType TInt32
    CUInt ->                                -- condition : TInterface "GLib" "IOCondition"
    FunPtr IOFuncC ->                       -- func : TInterface "GLib" "IOFunc"
    Ptr () ->                               -- user_data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- notify : TInterface "GLib" "DestroyNotify"
    IO Word32


ioAddWatch ::
    (MonadIO m) =>
    IOChannel ->                            -- channel
    Int32 ->                                -- priority
    [IOCondition] ->                        -- condition
    IOFunc ->                               -- func
    m Word32
ioAddWatch channel priority condition func = liftIO $ do
    let channel' = unsafeManagedPtrGetPtr channel
    let condition' = gflagsToWord condition
    func' <- mkIOFunc (iOFuncWrapper Nothing func)
    let user_data = castFunPtrToPtr func'
    let notify = safeFreeFunPtrPtr
    result <- g_io_add_watch_full channel' priority condition' func' user_data notify
    touchManagedPtr channel
    return result


-- function g_intern_string
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_intern_string" g_intern_string :: 
    CString ->                              -- string : TBasicType TUTF8
    IO CString


internString ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- string
    m T.Text
internString string = liftIO $ do
    maybeString <- case string of
        Nothing -> return nullPtr
        Just jString -> do
            jString' <- textToCString jString
            return jString'
    result <- g_intern_string maybeString
    checkUnexpectedReturnNULL "g_intern_string" result
    result' <- cstringToText result
    freeMem maybeString
    return result'


-- function g_intern_static_string
-- Args : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_intern_static_string" g_intern_static_string :: 
    CString ->                              -- string : TBasicType TUTF8
    IO CString


internStaticString ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- string
    m T.Text
internStaticString string = liftIO $ do
    maybeString <- case string of
        Nothing -> return nullPtr
        Just jString -> do
            jString' <- textToCString jString
            return jString'
    result <- g_intern_static_string maybeString
    checkUnexpectedReturnNULL "g_intern_static_string" result
    result' <- cstringToText result
    freeMem maybeString
    return result'


-- function g_int_hash
-- Args : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_int_hash" g_int_hash :: 
    Ptr () ->                               -- v : TBasicType TVoid
    IO Word32


intHash ::
    (MonadIO m) =>
    Ptr () ->                               -- v
    m Word32
intHash v = liftIO $ do
    result <- g_int_hash v
    return result


-- function g_int_equal
-- Args : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_int_equal" g_int_equal :: 
    Ptr () ->                               -- v1 : TBasicType TVoid
    Ptr () ->                               -- v2 : TBasicType TVoid
    IO CInt


intEqual ::
    (MonadIO m) =>
    Ptr () ->                               -- v1
    Ptr () ->                               -- v2
    m Bool
intEqual v1 v2 = liftIO $ do
    result <- g_int_equal v1 v2
    let result' = (/= 0) result
    return result'


-- function g_int64_hash
-- Args : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_int64_hash" g_int64_hash :: 
    Ptr () ->                               -- v : TBasicType TVoid
    IO Word32


int64Hash ::
    (MonadIO m) =>
    Ptr () ->                               -- v
    m Word32
int64Hash v = liftIO $ do
    result <- g_int64_hash v
    return result


-- function g_int64_equal
-- Args : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_int64_equal" g_int64_equal :: 
    Ptr () ->                               -- v1 : TBasicType TVoid
    Ptr () ->                               -- v2 : TBasicType TVoid
    IO CInt


int64Equal ::
    (MonadIO m) =>
    Ptr () ->                               -- v1
    Ptr () ->                               -- v2
    m Bool
int64Equal v1 v2 = liftIO $ do
    result <- g_int64_equal v1 v2
    let result' = (/= 0) result
    return result'


-- function g_idle_source_new
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "GLib" "Source"
-- throws : False
-- Skip return : False

foreign import ccall "g_idle_source_new" g_idle_source_new :: 
    IO (Ptr Source)


idleSourceNew ::
    (MonadIO m) =>
    m Source
idleSourceNew  = liftIO $ do
    result <- g_idle_source_new
    checkUnexpectedReturnNULL "g_idle_source_new" result
    result' <- (wrapBoxed Source) result
    return result'


-- function g_idle_remove_by_data
-- Args : [Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_idle_remove_by_data" g_idle_remove_by_data :: 
    Ptr () ->                               -- data : TBasicType TVoid
    IO CInt


idleRemoveByData ::
    (MonadIO m) =>
    Ptr () ->                               -- data
    m Bool
idleRemoveByData data_ = liftIO $ do
    result <- g_idle_remove_by_data data_
    let result' = (/= 0) result
    return result'


-- function g_idle_add_full
-- Args : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "SourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "notify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "SourceFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 2, argDestroy = 3, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_idle_add_full" g_idle_add_full :: 
    Int32 ->                                -- priority : TBasicType TInt32
    FunPtr SourceFuncC ->                   -- function : TInterface "GLib" "SourceFunc"
    Ptr () ->                               -- data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- notify : TInterface "GLib" "DestroyNotify"
    IO Word32


idleAdd ::
    (MonadIO m) =>
    Int32 ->                                -- priority
    SourceFunc ->                           -- function
    m Word32
idleAdd priority function = liftIO $ do
    function' <- mkSourceFunc (sourceFuncWrapper Nothing function)
    let data_ = castFunPtrToPtr function'
    let notify = safeFreeFunPtrPtr
    result <- g_idle_add_full priority function' data_ notify
    return result


-- function g_iconv
-- Args : [Arg {argName = "converter", argType = TInterface "GLib" "IConv", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "inbuf", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "inbytes_left", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "outbuf", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "outbytes_left", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "converter", argType = TInterface "GLib" "IConv", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "inbuf", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "inbytes_left", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "outbuf", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "outbytes_left", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_iconv" g_iconv :: 
    Ptr IConv ->                            -- converter : TInterface "GLib" "IConv"
    CString ->                              -- inbuf : TBasicType TUTF8
    Word64 ->                               -- inbytes_left : TBasicType TUInt64
    CString ->                              -- outbuf : TBasicType TUTF8
    Word64 ->                               -- outbytes_left : TBasicType TUInt64
    IO Word64


iconv ::
    (MonadIO m) =>
    IConv ->                                -- converter
    T.Text ->                               -- inbuf
    Word64 ->                               -- inbytes_left
    T.Text ->                               -- outbuf
    Word64 ->                               -- outbytes_left
    m Word64
iconv converter inbuf inbytes_left outbuf outbytes_left = liftIO $ do
    let converter' = unsafeManagedPtrGetPtr converter
    inbuf' <- textToCString inbuf
    outbuf' <- textToCString outbuf
    result <- g_iconv converter' inbuf' inbytes_left outbuf' outbytes_left
    touchManagedPtr converter
    freeMem inbuf'
    freeMem outbuf'
    return result


-- function g_hostname_to_unicode
-- Args : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_hostname_to_unicode" g_hostname_to_unicode :: 
    CString ->                              -- hostname : TBasicType TUTF8
    IO CString


hostnameToUnicode ::
    (MonadIO m) =>
    T.Text ->                               -- hostname
    m T.Text
hostnameToUnicode hostname = liftIO $ do
    hostname' <- textToCString hostname
    result <- g_hostname_to_unicode hostname'
    checkUnexpectedReturnNULL "g_hostname_to_unicode" result
    result' <- cstringToText result
    freeMem result
    freeMem hostname'
    return result'


-- function g_hostname_to_ascii
-- Args : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_hostname_to_ascii" g_hostname_to_ascii :: 
    CString ->                              -- hostname : TBasicType TUTF8
    IO CString


hostnameToAscii ::
    (MonadIO m) =>
    T.Text ->                               -- hostname
    m T.Text
hostnameToAscii hostname = liftIO $ do
    hostname' <- textToCString hostname
    result <- g_hostname_to_ascii hostname'
    checkUnexpectedReturnNULL "g_hostname_to_ascii" result
    result' <- cstringToText result
    freeMem result
    freeMem hostname'
    return result'


-- function g_hostname_is_non_ascii
-- Args : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hostname_is_non_ascii" g_hostname_is_non_ascii :: 
    CString ->                              -- hostname : TBasicType TUTF8
    IO CInt


hostnameIsNonAscii ::
    (MonadIO m) =>
    T.Text ->                               -- hostname
    m Bool
hostnameIsNonAscii hostname = liftIO $ do
    hostname' <- textToCString hostname
    result <- g_hostname_is_non_ascii hostname'
    let result' = (/= 0) result
    freeMem hostname'
    return result'


-- function g_hostname_is_ip_address
-- Args : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hostname_is_ip_address" g_hostname_is_ip_address :: 
    CString ->                              -- hostname : TBasicType TUTF8
    IO CInt


hostnameIsIpAddress ::
    (MonadIO m) =>
    T.Text ->                               -- hostname
    m Bool
hostnameIsIpAddress hostname = liftIO $ do
    hostname' <- textToCString hostname
    result <- g_hostname_is_ip_address hostname'
    let result' = (/= 0) result
    freeMem hostname'
    return result'


-- function g_hostname_is_ascii_encoded
-- Args : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hostname_is_ascii_encoded" g_hostname_is_ascii_encoded :: 
    CString ->                              -- hostname : TBasicType TUTF8
    IO CInt


hostnameIsAsciiEncoded ::
    (MonadIO m) =>
    T.Text ->                               -- hostname
    m Bool
hostnameIsAsciiEncoded hostname = liftIO $ do
    hostname' <- textToCString hostname
    result <- g_hostname_is_ascii_encoded hostname'
    let result' = (/= 0) result
    freeMem hostname'
    return result'


-- function g_hook_unref
-- Args : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_unref" g_hook_unref :: 
    Ptr HookList ->                         -- hook_list : TInterface "GLib" "HookList"
    Ptr Hook ->                             -- hook : TInterface "GLib" "Hook"
    IO ()


hookUnref ::
    (MonadIO m) =>
    HookList ->                             -- hook_list
    Hook ->                                 -- hook
    m ()
hookUnref hook_list hook = liftIO $ do
    let hook_list' = unsafeManagedPtrGetPtr hook_list
    let hook' = unsafeManagedPtrGetPtr hook
    g_hook_unref hook_list' hook'
    touchManagedPtr hook_list
    touchManagedPtr hook
    return ()


-- function g_hook_prepend
-- Args : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_prepend" g_hook_prepend :: 
    Ptr HookList ->                         -- hook_list : TInterface "GLib" "HookList"
    Ptr Hook ->                             -- hook : TInterface "GLib" "Hook"
    IO ()


hookPrepend ::
    (MonadIO m) =>
    HookList ->                             -- hook_list
    Hook ->                                 -- hook
    m ()
hookPrepend hook_list hook = liftIO $ do
    let hook_list' = unsafeManagedPtrGetPtr hook_list
    let hook' = unsafeManagedPtrGetPtr hook
    g_hook_prepend hook_list' hook'
    touchManagedPtr hook_list
    touchManagedPtr hook
    return ()


-- function g_hook_insert_before
-- Args : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "sibling", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "sibling", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_insert_before" g_hook_insert_before :: 
    Ptr HookList ->                         -- hook_list : TInterface "GLib" "HookList"
    Ptr Hook ->                             -- sibling : TInterface "GLib" "Hook"
    Ptr Hook ->                             -- hook : TInterface "GLib" "Hook"
    IO ()


hookInsertBefore ::
    (MonadIO m) =>
    HookList ->                             -- hook_list
    Hook ->                                 -- sibling
    Hook ->                                 -- hook
    m ()
hookInsertBefore hook_list sibling hook = liftIO $ do
    let hook_list' = unsafeManagedPtrGetPtr hook_list
    let sibling' = unsafeManagedPtrGetPtr sibling
    let hook' = unsafeManagedPtrGetPtr hook
    g_hook_insert_before hook_list' sibling' hook'
    touchManagedPtr hook_list
    touchManagedPtr sibling
    touchManagedPtr hook
    return ()


-- function g_hook_free
-- Args : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_free" g_hook_free :: 
    Ptr HookList ->                         -- hook_list : TInterface "GLib" "HookList"
    Ptr Hook ->                             -- hook : TInterface "GLib" "Hook"
    IO ()


hookFree ::
    (MonadIO m) =>
    HookList ->                             -- hook_list
    Hook ->                                 -- hook
    m ()
hookFree hook_list hook = liftIO $ do
    let hook_list' = unsafeManagedPtrGetPtr hook_list
    let hook' = unsafeManagedPtrGetPtr hook
    g_hook_free hook_list' hook'
    touchManagedPtr hook_list
    touchManagedPtr hook
    return ()


-- function g_hook_destroy_link
-- Args : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook", argType = TInterface "GLib" "Hook", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_destroy_link" g_hook_destroy_link :: 
    Ptr HookList ->                         -- hook_list : TInterface "GLib" "HookList"
    Ptr Hook ->                             -- hook : TInterface "GLib" "Hook"
    IO ()


hookDestroyLink ::
    (MonadIO m) =>
    HookList ->                             -- hook_list
    Hook ->                                 -- hook
    m ()
hookDestroyLink hook_list hook = liftIO $ do
    let hook_list' = unsafeManagedPtrGetPtr hook_list
    let hook' = unsafeManagedPtrGetPtr hook
    g_hook_destroy_link hook_list' hook'
    touchManagedPtr hook_list
    touchManagedPtr hook
    return ()


-- function g_hook_destroy
-- Args : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook_id", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hook_list", argType = TInterface "GLib" "HookList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hook_id", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hook_destroy" g_hook_destroy :: 
    Ptr HookList ->                         -- hook_list : TInterface "GLib" "HookList"
    Word64 ->                               -- hook_id : TBasicType TUInt64
    IO CInt


hookDestroy ::
    (MonadIO m) =>
    HookList ->                             -- hook_list
    Word64 ->                               -- hook_id
    m Bool
hookDestroy hook_list hook_id = liftIO $ do
    let hook_list' = unsafeManagedPtrGetPtr hook_list
    result <- g_hook_destroy hook_list' hook_id
    let result' = (/= 0) result
    touchManagedPtr hook_list
    return result'


-- function g_hash_table_unref
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_unref" g_hash_table_unref :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    IO ()


hashTableUnref ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    m ()
hashTableUnref hash_table = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    g_hash_table_unref hash_table''''
    unrefGHashTable hash_table''''
    return ()


-- function g_hash_table_steal_all
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_steal_all" g_hash_table_steal_all :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    IO ()


hashTableStealAll ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    m ()
hashTableStealAll hash_table = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    g_hash_table_steal_all hash_table''''
    unrefGHashTable hash_table''''
    return ()


-- function g_hash_table_steal
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_steal" g_hash_table_steal :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    Ptr () ->                               -- key : TBasicType TVoid
    IO CInt


hashTableSteal ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    Ptr () ->                               -- key
    m Bool
hashTableSteal hash_table key = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    result <- g_hash_table_steal hash_table'''' key
    let result' = (/= 0) result
    unrefGHashTable hash_table''''
    return result'


-- function g_hash_table_size
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_size" g_hash_table_size :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    IO Word32


hashTableSize ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    m Word32
hashTableSize hash_table = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    result <- g_hash_table_size hash_table''''
    unrefGHashTable hash_table''''
    return result


-- function g_hash_table_replace
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_replace" g_hash_table_replace :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    Ptr () ->                               -- key : TBasicType TVoid
    Ptr () ->                               -- value : TBasicType TVoid
    IO CInt


hashTableReplace ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    Ptr () ->                               -- key
    Ptr () ->                               -- value
    m Bool
hashTableReplace hash_table key value = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    result <- g_hash_table_replace hash_table'''' key value
    let result' = (/= 0) result
    unrefGHashTable hash_table''''
    return result'


-- function g_hash_table_remove_all
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_remove_all" g_hash_table_remove_all :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    IO ()


hashTableRemoveAll ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    m ()
hashTableRemoveAll hash_table = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    g_hash_table_remove_all hash_table''''
    unrefGHashTable hash_table''''
    return ()


-- function g_hash_table_remove
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_remove" g_hash_table_remove :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    Ptr () ->                               -- key : TBasicType TVoid
    IO CInt


hashTableRemove ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    Ptr () ->                               -- key
    m Bool
hashTableRemove hash_table key = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    result <- g_hash_table_remove hash_table'''' key
    let result' = (/= 0) result
    unrefGHashTable hash_table''''
    return result'


-- function g_hash_table_lookup_extended
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lookup_key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "orig_key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lookup_key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "orig_key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_lookup_extended" g_hash_table_lookup_extended :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    Ptr () ->                               -- lookup_key : TBasicType TVoid
    Ptr () ->                               -- orig_key : TBasicType TVoid
    Ptr () ->                               -- value : TBasicType TVoid
    IO CInt


hashTableLookupExtended ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    Ptr () ->                               -- lookup_key
    Maybe (Ptr ()) ->                       -- orig_key
    Maybe (Ptr ()) ->                       -- value
    m Bool
hashTableLookupExtended hash_table lookup_key orig_key value = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    maybeOrig_key <- case orig_key of
        Nothing -> return nullPtr
        Just jOrig_key -> do
            return jOrig_key
    maybeValue <- case value of
        Nothing -> return nullPtr
        Just jValue -> do
            return jValue
    result <- g_hash_table_lookup_extended hash_table'''' lookup_key maybeOrig_key maybeValue
    let result' = (/= 0) result
    unrefGHashTable hash_table''''
    return result'


-- function g_hash_table_insert
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_insert" g_hash_table_insert :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    Ptr () ->                               -- key : TBasicType TVoid
    Ptr () ->                               -- value : TBasicType TVoid
    IO CInt


hashTableInsert ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    Ptr () ->                               -- key
    Ptr () ->                               -- value
    m Bool
hashTableInsert hash_table key value = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    result <- g_hash_table_insert hash_table'''' key value
    let result' = (/= 0) result
    unrefGHashTable hash_table''''
    return result'


-- function g_hash_table_destroy
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_destroy" g_hash_table_destroy :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    IO ()


hashTableDestroy ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    m ()
hashTableDestroy hash_table = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    g_hash_table_destroy hash_table''''
    unrefGHashTable hash_table''''
    return ()


-- function g_hash_table_contains
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_contains" g_hash_table_contains :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    Ptr () ->                               -- key : TBasicType TVoid
    IO CInt


hashTableContains ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    Ptr () ->                               -- key
    m Bool
hashTableContains hash_table key = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    result <- g_hash_table_contains hash_table'''' key
    let result' = (/= 0) result
    unrefGHashTable hash_table''''
    return result'


-- function g_hash_table_add
-- Args : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "hash_table", argType = TGHash (TBasicType TVoid) (TBasicType TVoid), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_hash_table_add" g_hash_table_add :: 
    Ptr (GHashTable (Ptr ()) (Ptr ())) ->   -- hash_table : TGHash (TBasicType TVoid) (TBasicType TVoid)
    Ptr () ->                               -- key : TBasicType TVoid
    IO CInt


hashTableAdd ::
    (MonadIO m) =>
    Map.Map (Ptr ()) (Ptr ()) ->            -- hash_table
    Ptr () ->                               -- key
    m Bool
hashTableAdd hash_table key = liftIO $ do
    let hash_table' = Map.toList hash_table
    let hash_table'' = mapFirst ptrPackPtr hash_table'
    let hash_table''' = mapSecond ptrPackPtr hash_table''
    hash_table'''' <- packGHashTable gDirectHash gDirectEqual Nothing Nothing hash_table'''
    result <- g_hash_table_add hash_table'''' key
    let result' = (/= 0) result
    unrefGHashTable hash_table''''
    return result'


-- function g_getenv
-- Args : [Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_getenv" g_getenv :: 
    CString ->                              -- variable : TBasicType TUTF8
    IO CString


getenv ::
    (MonadIO m) =>
    T.Text ->                               -- variable
    m T.Text
getenv variable = liftIO $ do
    variable' <- textToCString variable
    result <- g_getenv variable'
    checkUnexpectedReturnNULL "g_getenv" result
    result' <- cstringToText result
    freeMem variable'
    return result'


-- function g_get_user_special_dir
-- Args : [Arg {argName = "directory", argType = TInterface "GLib" "UserDirectory", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "directory", argType = TInterface "GLib" "UserDirectory", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_user_special_dir" g_get_user_special_dir :: 
    CUInt ->                                -- directory : TInterface "GLib" "UserDirectory"
    IO CString


getUserSpecialDir ::
    (MonadIO m) =>
    UserDirectory ->                        -- directory
    m T.Text
getUserSpecialDir directory = liftIO $ do
    let directory' = (fromIntegral . fromEnum) directory
    result <- g_get_user_special_dir directory'
    checkUnexpectedReturnNULL "g_get_user_special_dir" result
    result' <- cstringToText result
    return result'


-- function g_get_user_runtime_dir
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_user_runtime_dir" g_get_user_runtime_dir :: 
    IO CString


getUserRuntimeDir ::
    (MonadIO m) =>
    m T.Text
getUserRuntimeDir  = liftIO $ do
    result <- g_get_user_runtime_dir
    checkUnexpectedReturnNULL "g_get_user_runtime_dir" result
    result' <- cstringToText result
    return result'


-- function g_get_user_name
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_user_name" g_get_user_name :: 
    IO CString


getUserName ::
    (MonadIO m) =>
    m T.Text
getUserName  = liftIO $ do
    result <- g_get_user_name
    checkUnexpectedReturnNULL "g_get_user_name" result
    result' <- cstringToText result
    return result'


-- function g_get_user_data_dir
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_user_data_dir" g_get_user_data_dir :: 
    IO CString


getUserDataDir ::
    (MonadIO m) =>
    m T.Text
getUserDataDir  = liftIO $ do
    result <- g_get_user_data_dir
    checkUnexpectedReturnNULL "g_get_user_data_dir" result
    result' <- cstringToText result
    return result'


-- function g_get_user_config_dir
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_user_config_dir" g_get_user_config_dir :: 
    IO CString


getUserConfigDir ::
    (MonadIO m) =>
    m T.Text
getUserConfigDir  = liftIO $ do
    result <- g_get_user_config_dir
    checkUnexpectedReturnNULL "g_get_user_config_dir" result
    result' <- cstringToText result
    return result'


-- function g_get_user_cache_dir
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_user_cache_dir" g_get_user_cache_dir :: 
    IO CString


getUserCacheDir ::
    (MonadIO m) =>
    m T.Text
getUserCacheDir  = liftIO $ do
    result <- g_get_user_cache_dir
    checkUnexpectedReturnNULL "g_get_user_cache_dir" result
    result' <- cstringToText result
    return result'


-- function g_get_tmp_dir
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_tmp_dir" g_get_tmp_dir :: 
    IO CString


getTmpDir ::
    (MonadIO m) =>
    m T.Text
getTmpDir  = liftIO $ do
    result <- g_get_tmp_dir
    checkUnexpectedReturnNULL "g_get_tmp_dir" result
    result' <- cstringToText result
    return result'


-- function g_get_system_data_dirs
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_get_system_data_dirs" g_get_system_data_dirs :: 
    IO (Ptr CString)


getSystemDataDirs ::
    (MonadIO m) =>
    m [T.Text]
getSystemDataDirs  = liftIO $ do
    result <- g_get_system_data_dirs
    checkUnexpectedReturnNULL "g_get_system_data_dirs" result
    result' <- unpackZeroTerminatedUTF8CArray result
    return result'


-- function g_get_system_config_dirs
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_get_system_config_dirs" g_get_system_config_dirs :: 
    IO (Ptr CString)


getSystemConfigDirs ::
    (MonadIO m) =>
    m [T.Text]
getSystemConfigDirs  = liftIO $ do
    result <- g_get_system_config_dirs
    checkUnexpectedReturnNULL "g_get_system_config_dirs" result
    result' <- unpackZeroTerminatedUTF8CArray result
    return result'


-- function g_get_real_time
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_get_real_time" g_get_real_time :: 
    IO Int64


getRealTime ::
    (MonadIO m) =>
    m Int64
getRealTime  = liftIO $ do
    result <- g_get_real_time
    return result


-- function g_get_real_name
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_real_name" g_get_real_name :: 
    IO CString


getRealName ::
    (MonadIO m) =>
    m T.Text
getRealName  = liftIO $ do
    result <- g_get_real_name
    checkUnexpectedReturnNULL "g_get_real_name" result
    result' <- cstringToText result
    return result'


-- function g_get_prgname
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_prgname" g_get_prgname :: 
    IO CString


getPrgname ::
    (MonadIO m) =>
    m T.Text
getPrgname  = liftIO $ do
    result <- g_get_prgname
    checkUnexpectedReturnNULL "g_get_prgname" result
    result' <- cstringToText result
    return result'


-- function g_get_num_processors
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_get_num_processors" g_get_num_processors :: 
    IO Word32


getNumProcessors ::
    (MonadIO m) =>
    m Word32
getNumProcessors  = liftIO $ do
    result <- g_get_num_processors
    return result


-- function g_get_monotonic_time
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_get_monotonic_time" g_get_monotonic_time :: 
    IO Int64


getMonotonicTime ::
    (MonadIO m) =>
    m Int64
getMonotonicTime  = liftIO $ do
    result <- g_get_monotonic_time
    return result


-- function g_get_locale_variants
-- Args : [Arg {argName = "locale", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "locale", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_get_locale_variants" g_get_locale_variants :: 
    CString ->                              -- locale : TBasicType TUTF8
    IO (Ptr CString)


getLocaleVariants ::
    (MonadIO m) =>
    T.Text ->                               -- locale
    m [T.Text]
getLocaleVariants locale = liftIO $ do
    locale' <- textToCString locale
    result <- g_get_locale_variants locale'
    checkUnexpectedReturnNULL "g_get_locale_variants" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    freeMem locale'
    return result'


-- function g_get_language_names
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_get_language_names" g_get_language_names :: 
    IO (Ptr CString)


getLanguageNames ::
    (MonadIO m) =>
    m [T.Text]
getLanguageNames  = liftIO $ do
    result <- g_get_language_names
    checkUnexpectedReturnNULL "g_get_language_names" result
    result' <- unpackZeroTerminatedUTF8CArray result
    return result'


-- function g_get_host_name
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_host_name" g_get_host_name :: 
    IO CString


getHostName ::
    (MonadIO m) =>
    m T.Text
getHostName  = liftIO $ do
    result <- g_get_host_name
    checkUnexpectedReturnNULL "g_get_host_name" result
    result' <- cstringToText result
    return result'


-- function g_get_home_dir
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_home_dir" g_get_home_dir :: 
    IO CString


getHomeDir ::
    (MonadIO m) =>
    m T.Text
getHomeDir  = liftIO $ do
    result <- g_get_home_dir
    checkUnexpectedReturnNULL "g_get_home_dir" result
    result' <- cstringToText result
    return result'


-- function g_get_filename_charsets
-- Args : [Arg {argName = "charsets", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "charsets", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_get_filename_charsets" g_get_filename_charsets :: 
    CString ->                              -- charsets : TBasicType TUTF8
    IO CInt


getFilenameCharsets ::
    (MonadIO m) =>
    T.Text ->                               -- charsets
    m Bool
getFilenameCharsets charsets = liftIO $ do
    charsets' <- textToCString charsets
    result <- g_get_filename_charsets charsets'
    let result' = (/= 0) result
    freeMem charsets'
    return result'


-- function g_get_environ
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_get_environ" g_get_environ :: 
    IO (Ptr CString)


getEnviron ::
    (MonadIO m) =>
    m [T.Text]
getEnviron  = liftIO $ do
    result <- g_get_environ
    checkUnexpectedReturnNULL "g_get_environ" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    return result'


-- function g_get_current_time
-- Args : [Arg {argName = "result", argType = TInterface "GLib" "TimeVal", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "result", argType = TInterface "GLib" "TimeVal", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_get_current_time" g_get_current_time :: 
    Ptr TimeVal ->                          -- result : TInterface "GLib" "TimeVal"
    IO ()


getCurrentTime ::
    (MonadIO m) =>
    TimeVal ->                              -- result
    m ()
getCurrentTime result_ = liftIO $ do
    let result_' = unsafeManagedPtrGetPtr result_
    g_get_current_time result_'
    touchManagedPtr result_
    return ()


-- function g_get_current_dir
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_current_dir" g_get_current_dir :: 
    IO CString


getCurrentDir ::
    (MonadIO m) =>
    m T.Text
getCurrentDir  = liftIO $ do
    result <- g_get_current_dir
    checkUnexpectedReturnNULL "g_get_current_dir" result
    result' <- cstringToText result
    freeMem result
    return result'


-- function g_get_codeset
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_codeset" g_get_codeset :: 
    IO CString


getCodeset ::
    (MonadIO m) =>
    m T.Text
getCodeset  = liftIO $ do
    result <- g_get_codeset
    checkUnexpectedReturnNULL "g_get_codeset" result
    result' <- cstringToText result
    freeMem result
    return result'


-- function g_get_charset
-- Args : [Arg {argName = "charset", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_get_charset" g_get_charset :: 
    Ptr CString ->                          -- charset : TBasicType TUTF8
    IO CInt


getCharset ::
    (MonadIO m) =>
    m (Bool,T.Text)
getCharset  = liftIO $ do
    charset <- allocMem :: IO (Ptr CString)
    result <- g_get_charset charset
    let result' = (/= 0) result
    charset' <- peek charset
    charset'' <- cstringToText charset'
    freeMem charset
    return (result', charset'')


-- function g_get_application_name
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_get_application_name" g_get_application_name :: 
    IO CString


getApplicationName ::
    (MonadIO m) =>
    m T.Text
getApplicationName  = liftIO $ do
    result <- g_get_application_name
    checkUnexpectedReturnNULL "g_get_application_name" result
    result' <- cstringToText result
    return result'


-- function g_free
-- Args : [Arg {argName = "mem", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "mem", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_free" g_free :: 
    Ptr () ->                               -- mem : TBasicType TVoid
    IO ()


free ::
    (MonadIO m) =>
    Maybe (Ptr ()) ->                       -- mem
    m ()
free mem = liftIO $ do
    maybeMem <- case mem of
        Nothing -> return nullPtr
        Just jMem -> do
            return jMem
    g_free maybeMem
    return ()


-- function g_format_size_full
-- Args : [Arg {argName = "size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "GLib" "FormatSizeFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TInterface "GLib" "FormatSizeFlags", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_format_size_full" g_format_size_full :: 
    Word64 ->                               -- size : TBasicType TUInt64
    CUInt ->                                -- flags : TInterface "GLib" "FormatSizeFlags"
    IO CString


formatSizeFull ::
    (MonadIO m) =>
    Word64 ->                               -- size
    [FormatSizeFlags] ->                    -- flags
    m T.Text
formatSizeFull size flags = liftIO $ do
    let flags' = gflagsToWord flags
    result <- g_format_size_full size flags'
    checkUnexpectedReturnNULL "g_format_size_full" result
    result' <- cstringToText result
    freeMem result
    return result'


-- function g_format_size_for_display
-- Args : [Arg {argName = "size", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "size", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_format_size_for_display" g_format_size_for_display :: 
    Int64 ->                                -- size : TBasicType TInt64
    IO CString

{-# DEPRECATED formatSizeForDisplay ["(Since version 2.30)","This function is broken due to its use of SI","    suffixes to denote IEC units. Use g_format_size() instead."]#-}
formatSizeForDisplay ::
    (MonadIO m) =>
    Int64 ->                                -- size
    m T.Text
formatSizeForDisplay size = liftIO $ do
    result <- g_format_size_for_display size
    checkUnexpectedReturnNULL "g_format_size_for_display" result
    result' <- cstringToText result
    freeMem result
    return result'


-- function g_format_size
-- Args : [Arg {argName = "size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "size", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_format_size" g_format_size :: 
    Word64 ->                               -- size : TBasicType TUInt64
    IO CString


formatSize ::
    (MonadIO m) =>
    Word64 ->                               -- size
    m T.Text
formatSize size = liftIO $ do
    result <- g_format_size size
    checkUnexpectedReturnNULL "g_format_size" result
    result' <- cstringToText result
    freeMem result
    return result'


-- function g_find_program_in_path
-- Args : [Arg {argName = "program", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "program", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_find_program_in_path" g_find_program_in_path :: 
    CString ->                              -- program : TBasicType TUTF8
    IO CString


findProgramInPath ::
    (MonadIO m) =>
    T.Text ->                               -- program
    m T.Text
findProgramInPath program = liftIO $ do
    program' <- textToCString program
    result <- g_find_program_in_path program'
    checkUnexpectedReturnNULL "g_find_program_in_path" result
    result' <- cstringToText result
    freeMem result
    freeMem program'
    return result'


-- function g_filename_to_utf8
-- Args : [Arg {argName = "opsysstring", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "opsysstring", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_filename_to_utf8" g_filename_to_utf8 :: 
    CString ->                              -- opsysstring : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    Word64 ->                               -- bytes_read : TBasicType TUInt64
    Word64 ->                               -- bytes_written : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString


filenameToUtf8 ::
    (MonadIO m) =>
    T.Text ->                               -- opsysstring
    Int64 ->                                -- len
    Word64 ->                               -- bytes_read
    Word64 ->                               -- bytes_written
    m T.Text
filenameToUtf8 opsysstring len bytes_read bytes_written = liftIO $ do
    opsysstring' <- textToCString opsysstring
    onException (do
        result <- propagateGError $ g_filename_to_utf8 opsysstring' len bytes_read bytes_written
        checkUnexpectedReturnNULL "g_filename_to_utf8" result
        result' <- cstringToText result
        freeMem result
        freeMem opsysstring'
        return result'
     ) (do
        freeMem opsysstring'
     )


-- function g_filename_to_uri
-- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_filename_to_uri" g_filename_to_uri :: 
    CString ->                              -- filename : TBasicType TUTF8
    CString ->                              -- hostname : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString


filenameToUri ::
    (MonadIO m) =>
    T.Text ->                               -- filename
    Maybe (T.Text) ->                       -- hostname
    m T.Text
filenameToUri filename hostname = liftIO $ do
    filename' <- textToCString filename
    maybeHostname <- case hostname of
        Nothing -> return nullPtr
        Just jHostname -> do
            jHostname' <- textToCString jHostname
            return jHostname'
    onException (do
        result <- propagateGError $ g_filename_to_uri filename' maybeHostname
        checkUnexpectedReturnNULL "g_filename_to_uri" result
        result' <- cstringToText result
        freeMem result
        freeMem filename'
        freeMem maybeHostname
        return result'
     ) (do
        freeMem filename'
        freeMem maybeHostname
     )


-- function g_filename_from_utf8
-- Args : [Arg {argName = "utf8string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : [Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- hInArgs : [Arg {argName = "utf8string", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray False (-1) 3 (TBasicType TUInt8)
-- throws : True
-- Skip return : False

foreign import ccall "g_filename_from_utf8" g_filename_from_utf8 :: 
    CString ->                              -- utf8string : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    Ptr Word64 ->                           -- bytes_read : TBasicType TUInt64
    Ptr Word64 ->                           -- bytes_written : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Word8)


filenameFromUtf8 ::
    (MonadIO m) =>
    T.Text ->                               -- utf8string
    Int64 ->                                -- len
    m (ByteString,Word64)
filenameFromUtf8 utf8string len = liftIO $ do
    utf8string' <- textToCString utf8string
    bytes_read <- allocMem :: IO (Ptr Word64)
    bytes_written <- allocMem :: IO (Ptr Word64)
    onException (do
        result <- propagateGError $ g_filename_from_utf8 utf8string' len bytes_read bytes_written
        bytes_written' <- peek bytes_written
        checkUnexpectedReturnNULL "g_filename_from_utf8" result
        result' <- (unpackByteStringWithLength bytes_written') result
        freeMem result
        bytes_read' <- peek bytes_read
        freeMem utf8string'
        freeMem bytes_read
        freeMem bytes_written
        return (result', bytes_read')
     ) (do
        freeMem utf8string'
        freeMem bytes_read
        freeMem bytes_written
     )


-- function g_filename_from_uri
-- Args : [Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hostname", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "uri", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TFileName
-- throws : True
-- Skip return : False

foreign import ccall "g_filename_from_uri" g_filename_from_uri :: 
    CString ->                              -- uri : TBasicType TUTF8
    Ptr CString ->                          -- hostname : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString


filenameFromUri ::
    (MonadIO m) =>
    T.Text ->                               -- uri
    m ([Char],T.Text)
filenameFromUri uri = liftIO $ do
    uri' <- textToCString uri
    hostname <- allocMem :: IO (Ptr CString)
    onException (do
        result <- propagateGError $ g_filename_from_uri uri' hostname
        checkUnexpectedReturnNULL "g_filename_from_uri" result
        result' <- cstringToString result
        freeMem result
        hostname' <- peek hostname
        hostname'' <- cstringToText hostname'
        freeMem hostname'
        freeMem uri'
        freeMem hostname
        return (result', hostname'')
     ) (do
        freeMem uri'
        freeMem hostname
     )


-- function g_filename_display_name
-- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_filename_display_name" g_filename_display_name :: 
    CString ->                              -- filename : TBasicType TUTF8
    IO CString


filenameDisplayName ::
    (MonadIO m) =>
    T.Text ->                               -- filename
    m T.Text
filenameDisplayName filename = liftIO $ do
    filename' <- textToCString filename
    result <- g_filename_display_name filename'
    checkUnexpectedReturnNULL "g_filename_display_name" result
    result' <- cstringToText result
    freeMem result
    freeMem filename'
    return result'


-- function g_filename_display_basename
-- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_filename_display_basename" g_filename_display_basename :: 
    CString ->                              -- filename : TBasicType TUTF8
    IO CString


filenameDisplayBasename ::
    (MonadIO m) =>
    T.Text ->                               -- filename
    m T.Text
filenameDisplayBasename filename = liftIO $ do
    filename' <- textToCString filename
    result <- g_filename_display_basename filename'
    checkUnexpectedReturnNULL "g_filename_display_basename" result
    result' <- cstringToText result
    freeMem result
    freeMem filename'
    return result'


-- function g_file_test
-- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test", argType = TInterface "GLib" "FileTest", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "test", argType = TInterface "GLib" "FileTest", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_file_test" g_file_test :: 
    CString ->                              -- filename : TBasicType TUTF8
    CUInt ->                                -- test : TInterface "GLib" "FileTest"
    IO CInt


fileTest ::
    (MonadIO m) =>
    T.Text ->                               -- filename
    [FileTest] ->                           -- test
    m Bool
fileTest filename test = liftIO $ do
    filename' <- textToCString filename
    let test' = gflagsToWord test
    result <- g_file_test filename' test'
    let result' = (/= 0) result
    freeMem filename'
    return result'


-- function g_file_set_contents
-- Args : [Arg {argName = "filename", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "contents", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "contents", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_file_set_contents" g_file_set_contents :: 
    CString ->                              -- filename : TBasicType TFileName
    Ptr Word8 ->                            -- contents : TCArray False (-1) 2 (TBasicType TUInt8)
    Int64 ->                                -- length : TBasicType TInt64
    Ptr (Ptr GError) ->                     -- error
    IO CInt


fileSetContents ::
    (MonadIO m) =>
    [Char] ->                               -- filename
    ByteString ->                           -- contents
    m ()
fileSetContents filename contents = liftIO $ do
    let length_ = fromIntegral $ B.length contents
    filename' <- stringToCString filename
    contents' <- packByteString contents
    onException (do
        _ <- propagateGError $ g_file_set_contents filename' contents' length_
        freeMem filename'
        freeMem contents'
        return ()
     ) (do
        freeMem filename'
        freeMem contents'
     )


-- function g_file_read_link
-- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_file_read_link" g_file_read_link :: 
    CString ->                              -- filename : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CString


fileReadLink ::
    (MonadIO m) =>
    T.Text ->                               -- filename
    m T.Text
fileReadLink filename = liftIO $ do
    filename' <- textToCString filename
    onException (do
        result <- propagateGError $ g_file_read_link filename'
        checkUnexpectedReturnNULL "g_file_read_link" result
        result' <- cstringToText result
        freeMem result
        freeMem filename'
        return result'
     ) (do
        freeMem filename'
     )


-- function g_file_open_tmp
-- Args : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "name_used", argType = TBasicType TFileName, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : True
-- Skip return : False

foreign import ccall "g_file_open_tmp" g_file_open_tmp :: 
    CString ->                              -- tmpl : TBasicType TFileName
    Ptr CString ->                          -- name_used : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO Int32


fileOpenTmp ::
    (MonadIO m) =>
    Maybe ([Char]) ->                       -- tmpl
    m (Int32,[Char])
fileOpenTmp tmpl = liftIO $ do
    maybeTmpl <- case tmpl of
        Nothing -> return nullPtr
        Just jTmpl -> do
            jTmpl' <- stringToCString jTmpl
            return jTmpl'
    name_used <- allocMem :: IO (Ptr CString)
    onException (do
        result <- propagateGError $ g_file_open_tmp maybeTmpl name_used
        name_used' <- peek name_used
        name_used'' <- cstringToString name_used'
        freeMem name_used'
        freeMem maybeTmpl
        freeMem name_used
        return (result, name_used'')
     ) (do
        freeMem maybeTmpl
        freeMem name_used
     )


-- function g_file_get_contents
-- Args : [Arg {argName = "filename", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "contents", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : [Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_file_get_contents" g_file_get_contents :: 
    CString ->                              -- filename : TBasicType TFileName
    Ptr (Ptr Word8) ->                      -- contents : TCArray False (-1) 2 (TBasicType TUInt8)
    Ptr Word64 ->                           -- length : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CInt


fileGetContents ::
    (MonadIO m) =>
    [Char] ->                               -- filename
    m (ByteString)
fileGetContents filename = liftIO $ do
    filename' <- stringToCString filename
    contents <- allocMem :: IO (Ptr (Ptr Word8))
    length_ <- allocMem :: IO (Ptr Word64)
    onException (do
        _ <- propagateGError $ g_file_get_contents filename' contents length_
        length_' <- peek length_
        contents' <- peek contents
        contents'' <- (unpackByteStringWithLength length_') contents'
        freeMem contents'
        freeMem filename'
        freeMem contents
        freeMem length_
        return contents''
     ) (do
        freeMem filename'
        freeMem contents
        freeMem length_
     )


-- function g_file_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_file_error_quark" g_file_error_quark :: 
    IO Word32


fileErrorQuark ::
    (MonadIO m) =>
    m Word32
fileErrorQuark  = liftIO $ do
    result <- g_file_error_quark
    return result


-- function g_file_error_from_errno
-- Args : [Arg {argName = "err_no", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "err_no", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "FileError"
-- throws : False
-- Skip return : False

foreign import ccall "g_file_error_from_errno" g_file_error_from_errno :: 
    Int32 ->                                -- err_no : TBasicType TInt32
    IO CUInt


fileErrorFromErrno ::
    (MonadIO m) =>
    Int32 ->                                -- err_no
    m FileError
fileErrorFromErrno err_no = liftIO $ do
    result <- g_file_error_from_errno err_no
    let result' = (toEnum . fromIntegral) result
    return result'


-- function g_environ_unsetenv
-- Args : [Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_environ_unsetenv" g_environ_unsetenv :: 
    Ptr CString ->                          -- envp : TCArray True (-1) (-1) (TBasicType TUTF8)
    CString ->                              -- variable : TBasicType TUTF8
    IO (Ptr CString)


environUnsetenv ::
    (MonadIO m) =>
    Maybe ([T.Text]) ->                     -- envp
    T.Text ->                               -- variable
    m [T.Text]
environUnsetenv envp variable = liftIO $ do
    maybeEnvp <- case envp of
        Nothing -> return nullPtr
        Just jEnvp -> do
            jEnvp' <- packZeroTerminatedUTF8CArray jEnvp
            return jEnvp'
    variable' <- textToCString variable
    result <- g_environ_unsetenv maybeEnvp variable'
    checkUnexpectedReturnNULL "g_environ_unsetenv" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    freeMem variable'
    return result'


-- function g_environ_setenv
-- Args : [Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "overwrite", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "overwrite", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "g_environ_setenv" g_environ_setenv :: 
    Ptr CString ->                          -- envp : TCArray True (-1) (-1) (TBasicType TUTF8)
    CString ->                              -- variable : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    CInt ->                                 -- overwrite : TBasicType TBoolean
    IO (Ptr CString)


environSetenv ::
    (MonadIO m) =>
    Maybe ([T.Text]) ->                     -- envp
    T.Text ->                               -- variable
    T.Text ->                               -- value
    Bool ->                                 -- overwrite
    m [T.Text]
environSetenv envp variable value overwrite = liftIO $ do
    maybeEnvp <- case envp of
        Nothing -> return nullPtr
        Just jEnvp -> do
            jEnvp' <- packZeroTerminatedUTF8CArray jEnvp
            return jEnvp'
    variable' <- textToCString variable
    value' <- textToCString value
    let overwrite' = (fromIntegral . fromEnum) overwrite
    result <- g_environ_setenv maybeEnvp variable' value' overwrite'
    checkUnexpectedReturnNULL "g_environ_setenv" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    freeMem variable'
    freeMem value'
    return result'


-- function g_environ_getenv
-- Args : [Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "envp", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "variable", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_environ_getenv" g_environ_getenv :: 
    Ptr CString ->                          -- envp : TCArray True (-1) (-1) (TBasicType TUTF8)
    CString ->                              -- variable : TBasicType TUTF8
    IO CString


environGetenv ::
    (MonadIO m) =>
    Maybe ([T.Text]) ->                     -- envp
    T.Text ->                               -- variable
    m T.Text
environGetenv envp variable = liftIO $ do
    maybeEnvp <- case envp of
        Nothing -> return nullPtr
        Just jEnvp -> do
            jEnvp' <- packZeroTerminatedUTF8CArray jEnvp
            return jEnvp'
    variable' <- textToCString variable
    result <- g_environ_getenv maybeEnvp variable'
    checkUnexpectedReturnNULL "g_environ_getenv" result
    result' <- cstringToText result
    mapZeroTerminatedCArray freeMem maybeEnvp
    freeMem maybeEnvp
    freeMem variable'
    return result'


-- function g_dpgettext2
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "context", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_dpgettext2" g_dpgettext2 :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- context : TBasicType TUTF8
    CString ->                              -- msgid : TBasicType TUTF8
    IO CString


dpgettext2 ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- domain
    T.Text ->                               -- context
    T.Text ->                               -- msgid
    m T.Text
dpgettext2 domain context msgid = liftIO $ do
    maybeDomain <- case domain of
        Nothing -> return nullPtr
        Just jDomain -> do
            jDomain' <- textToCString jDomain
            return jDomain'
    context' <- textToCString context
    msgid' <- textToCString msgid
    result <- g_dpgettext2 maybeDomain context' msgid'
    checkUnexpectedReturnNULL "g_dpgettext2" result
    result' <- cstringToText result
    freeMem maybeDomain
    freeMem context'
    freeMem msgid'
    return result'


-- function g_dpgettext
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgctxtid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgidoffset", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgctxtid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgidoffset", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_dpgettext" g_dpgettext :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- msgctxtid : TBasicType TUTF8
    Word64 ->                               -- msgidoffset : TBasicType TUInt64
    IO CString


dpgettext ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- domain
    T.Text ->                               -- msgctxtid
    Word64 ->                               -- msgidoffset
    m T.Text
dpgettext domain msgctxtid msgidoffset = liftIO $ do
    maybeDomain <- case domain of
        Nothing -> return nullPtr
        Just jDomain -> do
            jDomain' <- textToCString jDomain
            return jDomain'
    msgctxtid' <- textToCString msgctxtid
    result <- g_dpgettext maybeDomain msgctxtid' msgidoffset
    checkUnexpectedReturnNULL "g_dpgettext" result
    result' <- cstringToText result
    freeMem maybeDomain
    freeMem msgctxtid'
    return result'


-- function g_double_hash
-- Args : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_double_hash" g_double_hash :: 
    Ptr () ->                               -- v : TBasicType TVoid
    IO Word32


doubleHash ::
    (MonadIO m) =>
    Ptr () ->                               -- v
    m Word32
doubleHash v = liftIO $ do
    result <- g_double_hash v
    return result


-- function g_double_equal
-- Args : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_double_equal" g_double_equal :: 
    Ptr () ->                               -- v1 : TBasicType TVoid
    Ptr () ->                               -- v2 : TBasicType TVoid
    IO CInt


doubleEqual ::
    (MonadIO m) =>
    Ptr () ->                               -- v1
    Ptr () ->                               -- v2
    m Bool
doubleEqual v1 v2 = liftIO $ do
    result <- g_double_equal v1 v2
    let result' = (/= 0) result
    return result'


-- function g_dngettext
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid_plural", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid_plural", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_dngettext" g_dngettext :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- msgid : TBasicType TUTF8
    CString ->                              -- msgid_plural : TBasicType TUTF8
    Word64 ->                               -- n : TBasicType TUInt64
    IO CString


dngettext ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- domain
    T.Text ->                               -- msgid
    T.Text ->                               -- msgid_plural
    Word64 ->                               -- n
    m T.Text
dngettext domain msgid msgid_plural n = liftIO $ do
    maybeDomain <- case domain of
        Nothing -> return nullPtr
        Just jDomain -> do
            jDomain' <- textToCString jDomain
            return jDomain'
    msgid' <- textToCString msgid
    msgid_plural' <- textToCString msgid_plural
    result <- g_dngettext maybeDomain msgid' msgid_plural' n
    checkUnexpectedReturnNULL "g_dngettext" result
    result' <- cstringToText result
    freeMem maybeDomain
    freeMem msgid'
    freeMem msgid_plural'
    return result'


-- function g_direct_hash
-- Args : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_direct_hash" g_direct_hash :: 
    Ptr () ->                               -- v : TBasicType TVoid
    IO Word32


directHash ::
    (MonadIO m) =>
    Maybe (Ptr ()) ->                       -- v
    m Word32
directHash v = liftIO $ do
    maybeV <- case v of
        Nothing -> return nullPtr
        Just jV -> do
            return jV
    result <- g_direct_hash maybeV
    return result


-- function g_direct_equal
-- Args : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "v1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "v2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_direct_equal" g_direct_equal :: 
    Ptr () ->                               -- v1 : TBasicType TVoid
    Ptr () ->                               -- v2 : TBasicType TVoid
    IO CInt


directEqual ::
    (MonadIO m) =>
    Maybe (Ptr ()) ->                       -- v1
    Maybe (Ptr ()) ->                       -- v2
    m Bool
directEqual v1 v2 = liftIO $ do
    maybeV1 <- case v1 of
        Nothing -> return nullPtr
        Just jV1 -> do
            return jV1
    maybeV2 <- case v2 of
        Nothing -> return nullPtr
        Just jV2 -> do
            return jV2
    result <- g_direct_equal maybeV1 maybeV2
    let result' = (/= 0) result
    return result'


-- function g_dir_make_tmp
-- Args : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "tmpl", argType = TBasicType TFileName, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TFileName
-- throws : True
-- Skip return : False

foreign import ccall "g_dir_make_tmp" g_dir_make_tmp :: 
    CString ->                              -- tmpl : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO CString


dirMakeTmp ::
    (MonadIO m) =>
    Maybe ([Char]) ->                       -- tmpl
    m [Char]
dirMakeTmp tmpl = liftIO $ do
    maybeTmpl <- case tmpl of
        Nothing -> return nullPtr
        Just jTmpl -> do
            jTmpl' <- stringToCString jTmpl
            return jTmpl'
    onException (do
        result <- propagateGError $ g_dir_make_tmp maybeTmpl
        checkUnexpectedReturnNULL "g_dir_make_tmp" result
        result' <- cstringToString result
        freeMem result
        freeMem maybeTmpl
        return result'
     ) (do
        freeMem maybeTmpl
     )


-- function g_dgettext
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_dgettext" g_dgettext :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- msgid : TBasicType TUTF8
    IO CString


dgettext ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- domain
    T.Text ->                               -- msgid
    m T.Text
dgettext domain msgid = liftIO $ do
    maybeDomain <- case domain of
        Nothing -> return nullPtr
        Just jDomain -> do
            jDomain' <- textToCString jDomain
            return jDomain'
    msgid' <- textToCString msgid
    result <- g_dgettext maybeDomain msgid'
    checkUnexpectedReturnNULL "g_dgettext" result
    result' <- cstringToText result
    freeMem maybeDomain
    freeMem msgid'
    return result'


-- function g_dcgettext
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "category", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "msgid", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "category", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_dcgettext" g_dcgettext :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- msgid : TBasicType TUTF8
    Int32 ->                                -- category : TBasicType TInt32
    IO CString


dcgettext ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- domain
    T.Text ->                               -- msgid
    Int32 ->                                -- category
    m T.Text
dcgettext domain msgid category = liftIO $ do
    maybeDomain <- case domain of
        Nothing -> return nullPtr
        Just jDomain -> do
            jDomain' <- textToCString jDomain
            return jDomain'
    msgid' <- textToCString msgid
    result <- g_dcgettext maybeDomain msgid' category
    checkUnexpectedReturnNULL "g_dcgettext" result
    result' <- cstringToText result
    freeMem maybeDomain
    freeMem msgid'
    return result'


-- function g_date_valid_year
-- Args : [Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_date_valid_year" g_date_valid_year :: 
    Word16 ->                               -- year : TBasicType TUInt16
    IO CInt


dateValidYear ::
    (MonadIO m) =>
    Word16 ->                               -- year
    m Bool
dateValidYear year = liftIO $ do
    result <- g_date_valid_year year
    let result' = (/= 0) result
    return result'


-- function g_date_valid_weekday
-- Args : [Arg {argName = "weekday", argType = TInterface "GLib" "DateWeekday", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "weekday", argType = TInterface "GLib" "DateWeekday", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_date_valid_weekday" g_date_valid_weekday :: 
    CUInt ->                                -- weekday : TInterface "GLib" "DateWeekday"
    IO CInt


dateValidWeekday ::
    (MonadIO m) =>
    DateWeekday ->                          -- weekday
    m Bool
dateValidWeekday weekday = liftIO $ do
    let weekday' = (fromIntegral . fromEnum) weekday
    result <- g_date_valid_weekday weekday'
    let result' = (/= 0) result
    return result'


-- function g_date_valid_month
-- Args : [Arg {argName = "month", argType = TInterface "GLib" "DateMonth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "month", argType = TInterface "GLib" "DateMonth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_date_valid_month" g_date_valid_month :: 
    CUInt ->                                -- month : TInterface "GLib" "DateMonth"
    IO CInt


dateValidMonth ::
    (MonadIO m) =>
    DateMonth ->                            -- month
    m Bool
dateValidMonth month = liftIO $ do
    let month' = (fromIntegral . fromEnum) month
    result <- g_date_valid_month month'
    let result' = (/= 0) result
    return result'


-- function g_date_valid_julian
-- Args : [Arg {argName = "julian_date", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "julian_date", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_date_valid_julian" g_date_valid_julian :: 
    Word32 ->                               -- julian_date : TBasicType TUInt32
    IO CInt


dateValidJulian ::
    (MonadIO m) =>
    Word32 ->                               -- julian_date
    m Bool
dateValidJulian julian_date = liftIO $ do
    result <- g_date_valid_julian julian_date
    let result' = (/= 0) result
    return result'


-- function g_date_valid_dmy
-- Args : [Arg {argName = "day", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "month", argType = TInterface "GLib" "DateMonth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "day", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "month", argType = TInterface "GLib" "DateMonth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_date_valid_dmy" g_date_valid_dmy :: 
    Word8 ->                                -- day : TBasicType TUInt8
    CUInt ->                                -- month : TInterface "GLib" "DateMonth"
    Word16 ->                               -- year : TBasicType TUInt16
    IO CInt


dateValidDmy ::
    (MonadIO m) =>
    Word8 ->                                -- day
    DateMonth ->                            -- month
    Word16 ->                               -- year
    m Bool
dateValidDmy day month year = liftIO $ do
    let month' = (fromIntegral . fromEnum) month
    result <- g_date_valid_dmy day month' year
    let result' = (/= 0) result
    return result'


-- function g_date_valid_day
-- Args : [Arg {argName = "day", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "day", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_date_valid_day" g_date_valid_day :: 
    Word8 ->                                -- day : TBasicType TUInt8
    IO CInt


dateValidDay ::
    (MonadIO m) =>
    Word8 ->                                -- day
    m Bool
dateValidDay day = liftIO $ do
    result <- g_date_valid_day day
    let result' = (/= 0) result
    return result'


-- function g_date_time_hash
-- Args : [Arg {argName = "datetime", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "datetime", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_date_time_hash" g_date_time_hash :: 
    Ptr () ->                               -- datetime : TBasicType TVoid
    IO Word32


dateTimeHash ::
    (MonadIO m) =>
    Ptr () ->                               -- datetime
    m Word32
dateTimeHash datetime = liftIO $ do
    result <- g_date_time_hash datetime
    return result


-- function g_date_time_equal
-- Args : [Arg {argName = "dt1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dt2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dt1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dt2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_date_time_equal" g_date_time_equal :: 
    Ptr () ->                               -- dt1 : TBasicType TVoid
    Ptr () ->                               -- dt2 : TBasicType TVoid
    IO CInt


dateTimeEqual ::
    (MonadIO m) =>
    Ptr () ->                               -- dt1
    Ptr () ->                               -- dt2
    m Bool
dateTimeEqual dt1 dt2 = liftIO $ do
    result <- g_date_time_equal dt1 dt2
    let result' = (/= 0) result
    return result'


-- function g_date_time_compare
-- Args : [Arg {argName = "dt1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dt2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dt1", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "dt2", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_date_time_compare" g_date_time_compare :: 
    Ptr () ->                               -- dt1 : TBasicType TVoid
    Ptr () ->                               -- dt2 : TBasicType TVoid
    IO Int32


dateTimeCompare ::
    (MonadIO m) =>
    Ptr () ->                               -- dt1
    Ptr () ->                               -- dt2
    m Int32
dateTimeCompare dt1 dt2 = liftIO $ do
    result <- g_date_time_compare dt1 dt2
    return result


-- function g_date_strftime
-- Args : [Arg {argName = "s", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "slen", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "format", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "date", argType = TInterface "GLib" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "s", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "slen", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "format", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "date", argType = TInterface "GLib" "Date", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_date_strftime" g_date_strftime :: 
    CString ->                              -- s : TBasicType TUTF8
    Word64 ->                               -- slen : TBasicType TUInt64
    CString ->                              -- format : TBasicType TUTF8
    Ptr Date ->                             -- date : TInterface "GLib" "Date"
    IO Word64


dateStrftime ::
    (MonadIO m) =>
    T.Text ->                               -- s
    Word64 ->                               -- slen
    T.Text ->                               -- format
    Date ->                                 -- date
    m Word64
dateStrftime s slen format date = liftIO $ do
    s' <- textToCString s
    format' <- textToCString format
    let date' = unsafeManagedPtrGetPtr date
    result <- g_date_strftime s' slen format' date'
    touchManagedPtr date
    freeMem s'
    freeMem format'
    return result


-- function g_date_is_leap_year
-- Args : [Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_date_is_leap_year" g_date_is_leap_year :: 
    Word16 ->                               -- year : TBasicType TUInt16
    IO CInt


dateIsLeapYear ::
    (MonadIO m) =>
    Word16 ->                               -- year
    m Bool
dateIsLeapYear year = liftIO $ do
    result <- g_date_is_leap_year year
    let result' = (/= 0) result
    return result'


-- function g_date_get_sunday_weeks_in_year
-- Args : [Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt8
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_sunday_weeks_in_year" g_date_get_sunday_weeks_in_year :: 
    Word16 ->                               -- year : TBasicType TUInt16
    IO Word8


dateGetSundayWeeksInYear ::
    (MonadIO m) =>
    Word16 ->                               -- year
    m Word8
dateGetSundayWeeksInYear year = liftIO $ do
    result <- g_date_get_sunday_weeks_in_year year
    return result


-- function g_date_get_monday_weeks_in_year
-- Args : [Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt8
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_monday_weeks_in_year" g_date_get_monday_weeks_in_year :: 
    Word16 ->                               -- year : TBasicType TUInt16
    IO Word8


dateGetMondayWeeksInYear ::
    (MonadIO m) =>
    Word16 ->                               -- year
    m Word8
dateGetMondayWeeksInYear year = liftIO $ do
    result <- g_date_get_monday_weeks_in_year year
    return result


-- function g_date_get_days_in_month
-- Args : [Arg {argName = "month", argType = TInterface "GLib" "DateMonth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "month", argType = TInterface "GLib" "DateMonth", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "year", argType = TBasicType TUInt16, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt8
-- throws : False
-- Skip return : False

foreign import ccall "g_date_get_days_in_month" g_date_get_days_in_month :: 
    CUInt ->                                -- month : TInterface "GLib" "DateMonth"
    Word16 ->                               -- year : TBasicType TUInt16
    IO Word8


dateGetDaysInMonth ::
    (MonadIO m) =>
    DateMonth ->                            -- month
    Word16 ->                               -- year
    m Word8
dateGetDaysInMonth month year = liftIO $ do
    let month' = (fromIntegral . fromEnum) month
    result <- g_date_get_days_in_month month' year
    return result


-- function g_dataset_id_set_data_full
-- Args : [Arg {argName = "dataset_location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy_func", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dataset_location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy_func", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_dataset_id_set_data_full" g_dataset_id_set_data_full :: 
    Ptr () ->                               -- dataset_location : TBasicType TVoid
    Word32 ->                               -- key_id : TBasicType TUInt32
    Ptr () ->                               -- data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- destroy_func : TInterface "GLib" "DestroyNotify"
    IO ()


datasetIdSetDataFull ::
    (MonadIO m) =>
    Ptr () ->                               -- dataset_location
    Word32 ->                               -- key_id
    Ptr () ->                               -- data
    DestroyNotify ->                        -- destroy_func
    m ()
datasetIdSetDataFull dataset_location key_id data_ destroy_func = liftIO $ do
    ptrdestroy_func <- callocMem :: IO (Ptr (FunPtr DestroyNotifyC))
    destroy_func' <- mkDestroyNotify (destroyNotifyWrapper (Just ptrdestroy_func) destroy_func)
    poke ptrdestroy_func destroy_func'
    g_dataset_id_set_data_full dataset_location key_id data_ destroy_func'
    return ()


-- function g_dataset_destroy
-- Args : [Arg {argName = "dataset_location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "dataset_location", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_dataset_destroy" g_dataset_destroy :: 
    Ptr () ->                               -- dataset_location : TBasicType TVoid
    IO ()


datasetDestroy ::
    (MonadIO m) =>
    Ptr () ->                               -- dataset_location
    m ()
datasetDestroy dataset_location = liftIO $ do
    g_dataset_destroy dataset_location
    return ()


-- function g_datalist_unset_flags
-- Args : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_datalist_unset_flags" g_datalist_unset_flags :: 
    Ptr Data ->                             -- datalist : TInterface "GLib" "Data"
    Word32 ->                               -- flags : TBasicType TUInt32
    IO ()


datalistUnsetFlags ::
    (MonadIO m) =>
    Data ->                                 -- datalist
    Word32 ->                               -- flags
    m ()
datalistUnsetFlags datalist flags = liftIO $ do
    let datalist' = unsafeManagedPtrGetPtr datalist
    g_datalist_unset_flags datalist' flags
    touchManagedPtr datalist
    return ()


-- function g_datalist_set_flags
-- Args : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "flags", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_datalist_set_flags" g_datalist_set_flags :: 
    Ptr Data ->                             -- datalist : TInterface "GLib" "Data"
    Word32 ->                               -- flags : TBasicType TUInt32
    IO ()


datalistSetFlags ::
    (MonadIO m) =>
    Data ->                                 -- datalist
    Word32 ->                               -- flags
    m ()
datalistSetFlags datalist flags = liftIO $ do
    let datalist' = unsafeManagedPtrGetPtr datalist
    g_datalist_set_flags datalist' flags
    touchManagedPtr datalist
    return ()


-- function g_datalist_init
-- Args : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_datalist_init" g_datalist_init :: 
    Ptr Data ->                             -- datalist : TInterface "GLib" "Data"
    IO ()


datalistInit ::
    (MonadIO m) =>
    Data ->                                 -- datalist
    m ()
datalistInit datalist = liftIO $ do
    let datalist' = unsafeManagedPtrGetPtr datalist
    g_datalist_init datalist'
    touchManagedPtr datalist
    return ()


-- function g_datalist_id_set_data_full
-- Args : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy_func", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy_func", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_datalist_id_set_data_full" g_datalist_id_set_data_full :: 
    Ptr Data ->                             -- datalist : TInterface "GLib" "Data"
    Word32 ->                               -- key_id : TBasicType TUInt32
    Ptr () ->                               -- data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- destroy_func : TInterface "GLib" "DestroyNotify"
    IO ()


datalistIdSetDataFull ::
    (MonadIO m) =>
    Data ->                                 -- datalist
    Word32 ->                               -- key_id
    Maybe (Ptr ()) ->                       -- data
    DestroyNotify ->                        -- destroy_func
    m ()
datalistIdSetDataFull datalist key_id data_ destroy_func = liftIO $ do
    let datalist' = unsafeManagedPtrGetPtr datalist
    maybeData_ <- case data_ of
        Nothing -> return nullPtr
        Just jData_ -> do
            return jData_
    ptrdestroy_func <- callocMem :: IO (Ptr (FunPtr DestroyNotifyC))
    destroy_func' <- mkDestroyNotify (destroyNotifyWrapper (Just ptrdestroy_func) destroy_func)
    poke ptrdestroy_func destroy_func'
    g_datalist_id_set_data_full datalist' key_id maybeData_ destroy_func'
    touchManagedPtr datalist
    return ()


-- function g_datalist_id_replace_data
-- Args : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "oldval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "old_destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key_id", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "oldval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "old_destroy", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_datalist_id_replace_data" g_datalist_id_replace_data :: 
    Ptr Data ->                             -- datalist : TInterface "GLib" "Data"
    Word32 ->                               -- key_id : TBasicType TUInt32
    Ptr () ->                               -- oldval : TBasicType TVoid
    Ptr () ->                               -- newval : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- destroy : TInterface "GLib" "DestroyNotify"
    FunPtr DestroyNotifyC ->                -- old_destroy : TInterface "GLib" "DestroyNotify"
    IO CInt


datalistIdReplaceData ::
    (MonadIO m) =>
    Data ->                                 -- datalist
    Word32 ->                               -- key_id
    Maybe (Ptr ()) ->                       -- oldval
    Maybe (Ptr ()) ->                       -- newval
    Maybe (DestroyNotify) ->                -- destroy
    Maybe (DestroyNotify) ->                -- old_destroy
    m Bool
datalistIdReplaceData datalist key_id oldval newval destroy old_destroy = liftIO $ do
    let datalist' = unsafeManagedPtrGetPtr datalist
    maybeOldval <- case oldval of
        Nothing -> return nullPtr
        Just jOldval -> do
            return jOldval
    maybeNewval <- case newval of
        Nothing -> return nullPtr
        Just jNewval -> do
            return jNewval
    ptrdestroy <- callocMem :: IO (Ptr (FunPtr DestroyNotifyC))
    maybeDestroy <- case destroy of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jDestroy -> do
            jDestroy' <- mkDestroyNotify (destroyNotifyWrapper (Just ptrdestroy) jDestroy)
            poke ptrdestroy jDestroy'
            return jDestroy'
    ptrold_destroy <- callocMem :: IO (Ptr (FunPtr DestroyNotifyC))
    maybeOld_destroy <- case old_destroy of
        Nothing -> return (castPtrToFunPtr nullPtr)
        Just jOld_destroy -> do
            jOld_destroy' <- mkDestroyNotify (destroyNotifyWrapper (Just ptrold_destroy) jOld_destroy)
            poke ptrold_destroy jOld_destroy'
            return jOld_destroy'
    result <- g_datalist_id_replace_data datalist' key_id maybeOldval maybeNewval maybeDestroy maybeOld_destroy
    let result' = (/= 0) result
    touchManagedPtr datalist
    return result'


-- function g_datalist_get_flags
-- Args : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_datalist_get_flags" g_datalist_get_flags :: 
    Ptr Data ->                             -- datalist : TInterface "GLib" "Data"
    IO Word32


datalistGetFlags ::
    (MonadIO m) =>
    Data ->                                 -- datalist
    m Word32
datalistGetFlags datalist = liftIO $ do
    let datalist' = unsafeManagedPtrGetPtr datalist
    result <- g_datalist_get_flags datalist'
    touchManagedPtr datalist
    return result


-- function g_datalist_clear
-- Args : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "datalist", argType = TInterface "GLib" "Data", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_datalist_clear" g_datalist_clear :: 
    Ptr Data ->                             -- datalist : TInterface "GLib" "Data"
    IO ()


datalistClear ::
    (MonadIO m) =>
    Data ->                                 -- datalist
    m ()
datalistClear datalist = liftIO $ do
    let datalist' = unsafeManagedPtrGetPtr datalist
    g_datalist_clear datalist'
    touchManagedPtr datalist
    return ()


-- function g_convert_with_iconv
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "converter", argType = TInterface "GLib" "IConv", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "converter", argType = TInterface "GLib" "IConv", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_convert_with_iconv" g_convert_with_iconv :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    Ptr IConv ->                            -- converter : TInterface "GLib" "IConv"
    Word64 ->                               -- bytes_read : TBasicType TUInt64
    Word64 ->                               -- bytes_written : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString


convertWithIconv ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    IConv ->                                -- converter
    Word64 ->                               -- bytes_read
    Word64 ->                               -- bytes_written
    m T.Text
convertWithIconv str len converter bytes_read bytes_written = liftIO $ do
    str' <- textToCString str
    let converter' = unsafeManagedPtrGetPtr converter
    onException (do
        result <- propagateGError $ g_convert_with_iconv str' len converter' bytes_read bytes_written
        checkUnexpectedReturnNULL "g_convert_with_iconv" result
        result' <- cstringToText result
        freeMem result
        touchManagedPtr converter
        freeMem str'
        return result'
     ) (do
        freeMem str'
     )


-- function g_convert_with_fallback
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "to_codeset", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "from_codeset", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fallback", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "to_codeset", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "from_codeset", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "fallback", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_convert_with_fallback" g_convert_with_fallback :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    CString ->                              -- to_codeset : TBasicType TUTF8
    CString ->                              -- from_codeset : TBasicType TUTF8
    CString ->                              -- fallback : TBasicType TUTF8
    Word64 ->                               -- bytes_read : TBasicType TUInt64
    Word64 ->                               -- bytes_written : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString


convertWithFallback ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    T.Text ->                               -- to_codeset
    T.Text ->                               -- from_codeset
    T.Text ->                               -- fallback
    Word64 ->                               -- bytes_read
    Word64 ->                               -- bytes_written
    m T.Text
convertWithFallback str len to_codeset from_codeset fallback bytes_read bytes_written = liftIO $ do
    str' <- textToCString str
    to_codeset' <- textToCString to_codeset
    from_codeset' <- textToCString from_codeset
    fallback' <- textToCString fallback
    onException (do
        result <- propagateGError $ g_convert_with_fallback str' len to_codeset' from_codeset' fallback' bytes_read bytes_written
        checkUnexpectedReturnNULL "g_convert_with_fallback" result
        result' <- cstringToText result
        freeMem result
        freeMem str'
        freeMem to_codeset'
        freeMem from_codeset'
        freeMem fallback'
        return result'
     ) (do
        freeMem str'
        freeMem to_codeset'
        freeMem from_codeset'
        freeMem fallback'
     )


-- function g_convert_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_convert_error_quark" g_convert_error_quark :: 
    IO Word32


convertErrorQuark ::
    (MonadIO m) =>
    m Word32
convertErrorQuark  = liftIO $ do
    result <- g_convert_error_quark
    return result


-- function g_convert
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "to_codeset", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "from_codeset", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "bytes_read", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "bytes_written", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "to_codeset", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "from_codeset", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : True
-- Skip return : False

foreign import ccall "g_convert" g_convert :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    CString ->                              -- to_codeset : TBasicType TUTF8
    CString ->                              -- from_codeset : TBasicType TUTF8
    Ptr Word64 ->                           -- bytes_read : TBasicType TUInt64
    Ptr Word64 ->                           -- bytes_written : TBasicType TUInt64
    Ptr (Ptr GError) ->                     -- error
    IO CString


convert ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    T.Text ->                               -- to_codeset
    T.Text ->                               -- from_codeset
    m (T.Text,Word64,Word64)
convert str len to_codeset from_codeset = liftIO $ do
    str' <- textToCString str
    to_codeset' <- textToCString to_codeset
    from_codeset' <- textToCString from_codeset
    bytes_read <- allocMem :: IO (Ptr Word64)
    bytes_written <- allocMem :: IO (Ptr Word64)
    onException (do
        result <- propagateGError $ g_convert str' len to_codeset' from_codeset' bytes_read bytes_written
        checkUnexpectedReturnNULL "g_convert" result
        result' <- cstringToText result
        freeMem result
        bytes_read' <- peek bytes_read
        bytes_written' <- peek bytes_written
        freeMem str'
        freeMem to_codeset'
        freeMem from_codeset'
        freeMem bytes_read
        freeMem bytes_written
        return (result', bytes_read', bytes_written')
     ) (do
        freeMem str'
        freeMem to_codeset'
        freeMem from_codeset'
        freeMem bytes_read
        freeMem bytes_written
     )


-- function g_compute_hmac_for_string
-- Args : [Arg {argName = "digest_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key_len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "key_len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "digest_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_compute_hmac_for_string" g_compute_hmac_for_string :: 
    CUInt ->                                -- digest_type : TInterface "GLib" "ChecksumType"
    Ptr Word8 ->                            -- key : TCArray False (-1) 2 (TBasicType TUInt8)
    Word64 ->                               -- key_len : TBasicType TUInt64
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- length : TBasicType TInt64
    IO CString


computeHmacForString ::
    (MonadIO m) =>
    ChecksumType ->                         -- digest_type
    ByteString ->                           -- key
    T.Text ->                               -- str
    Int64 ->                                -- length
    m T.Text
computeHmacForString digest_type key str length_ = liftIO $ do
    let key_len = fromIntegral $ B.length key
    let digest_type' = (fromIntegral . fromEnum) digest_type
    key' <- packByteString key
    str' <- textToCString str
    result <- g_compute_hmac_for_string digest_type' key' key_len str' length_
    checkUnexpectedReturnNULL "g_compute_hmac_for_string" result
    result' <- cstringToText result
    freeMem result
    freeMem key'
    freeMem str'
    return result'


-- function g_compute_hmac_for_data
-- Args : [Arg {argName = "digest_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key_len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "key_len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "digest_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "key", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TUInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_compute_hmac_for_data" g_compute_hmac_for_data :: 
    CUInt ->                                -- digest_type : TInterface "GLib" "ChecksumType"
    Ptr Word8 ->                            -- key : TCArray False (-1) 2 (TBasicType TUInt8)
    Word64 ->                               -- key_len : TBasicType TUInt64
    Word8 ->                                -- data : TBasicType TUInt8
    Word64 ->                               -- length : TBasicType TUInt64
    IO CString


computeHmacForData ::
    (MonadIO m) =>
    ChecksumType ->                         -- digest_type
    ByteString ->                           -- key
    Word8 ->                                -- data
    Word64 ->                               -- length
    m T.Text
computeHmacForData digest_type key data_ length_ = liftIO $ do
    let key_len = fromIntegral $ B.length key
    let digest_type' = (fromIntegral . fromEnum) digest_type
    key' <- packByteString key
    result <- g_compute_hmac_for_data digest_type' key' key_len data_ length_
    checkUnexpectedReturnNULL "g_compute_hmac_for_data" result
    result' <- cstringToText result
    freeMem result
    freeMem key'
    return result'


-- function g_compute_checksum_for_string
-- Args : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_compute_checksum_for_string" g_compute_checksum_for_string :: 
    CUInt ->                                -- checksum_type : TInterface "GLib" "ChecksumType"
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- length : TBasicType TInt64
    IO CString


computeChecksumForString ::
    (MonadIO m) =>
    ChecksumType ->                         -- checksum_type
    T.Text ->                               -- str
    Int64 ->                                -- length
    m T.Text
computeChecksumForString checksum_type str length_ = liftIO $ do
    let checksum_type' = (fromIntegral . fromEnum) checksum_type
    str' <- textToCString str
    result <- g_compute_checksum_for_string checksum_type' str' length_
    checkUnexpectedReturnNULL "g_compute_checksum_for_string" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_compute_checksum_for_data
-- Args : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "length", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TCArray False (-1) 2 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_compute_checksum_for_data" g_compute_checksum_for_data :: 
    CUInt ->                                -- checksum_type : TInterface "GLib" "ChecksumType"
    Ptr Word8 ->                            -- data : TCArray False (-1) 2 (TBasicType TUInt8)
    Word64 ->                               -- length : TBasicType TUInt64
    IO CString


computeChecksumForData ::
    (MonadIO m) =>
    ChecksumType ->                         -- checksum_type
    ByteString ->                           -- data
    m T.Text
computeChecksumForData checksum_type data_ = liftIO $ do
    let length_ = fromIntegral $ B.length data_
    let checksum_type' = (fromIntegral . fromEnum) checksum_type
    data_' <- packByteString data_
    result <- g_compute_checksum_for_data checksum_type' data_' length_
    checkUnexpectedReturnNULL "g_compute_checksum_for_data" result
    result' <- cstringToText result
    freeMem result
    freeMem data_'
    return result'


-- function g_compute_checksum_for_bytes
-- Args : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TInterface "GLib" "Bytes", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "data", argType = TInterface "GLib" "Bytes", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_compute_checksum_for_bytes" g_compute_checksum_for_bytes :: 
    CUInt ->                                -- checksum_type : TInterface "GLib" "ChecksumType"
    Ptr Bytes ->                            -- data : TInterface "GLib" "Bytes"
    IO CString


computeChecksumForBytes ::
    (MonadIO m) =>
    ChecksumType ->                         -- checksum_type
    Bytes ->                                -- data
    m T.Text
computeChecksumForBytes checksum_type data_ = liftIO $ do
    let checksum_type' = (fromIntegral . fromEnum) checksum_type
    let data_' = unsafeManagedPtrGetPtr data_
    result <- g_compute_checksum_for_bytes checksum_type' data_'
    checkUnexpectedReturnNULL "g_compute_checksum_for_bytes" result
    result' <- cstringToText result
    freeMem result
    touchManagedPtr data_
    return result'


-- function g_close
-- Args : [Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "fd", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "g_close" g_close :: 
    Int32 ->                                -- fd : TBasicType TInt32
    Ptr (Ptr GError) ->                     -- error
    IO CInt


close ::
    (MonadIO m) =>
    Int32 ->                                -- fd
    m ()
close fd = liftIO $ do
    onException (do
        _ <- propagateGError $ g_close fd
        return ()
     ) (do
        return ()
     )


-- function g_clear_error
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TVoid
-- throws : True
-- Skip return : False

foreign import ccall "g_clear_error" g_clear_error :: 
    Ptr (Ptr GError) ->                     -- error
    IO ()


clearError ::
    (MonadIO m) =>
    m ()
clearError  = liftIO $ do
    onException (do
        propagateGError $ g_clear_error
        return ()
     ) (do
        return ()
     )


-- function g_child_watch_source_new
-- Args : [Arg {argName = "pid", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pid", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "GLib" "Source"
-- throws : False
-- Skip return : False

foreign import ccall "g_child_watch_source_new" g_child_watch_source_new :: 
    Int32 ->                                -- pid : TBasicType TInt32
    IO (Ptr Source)


childWatchSourceNew ::
    (MonadIO m) =>
    Int32 ->                                -- pid
    m Source
childWatchSourceNew pid = liftIO $ do
    result <- g_child_watch_source_new pid
    checkUnexpectedReturnNULL "g_child_watch_source_new" result
    result' <- (wrapBoxed Source) result
    return result'


-- function g_child_watch_add_full
-- Args : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pid", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "ChildWatchFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing},Arg {argName = "data", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "notify", argType = TInterface "GLib" "DestroyNotify", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "priority", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pid", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "function", argType = TInterface "GLib" "ChildWatchFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeNotified, argClosure = 3, argDestroy = 4, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_child_watch_add_full" g_child_watch_add_full :: 
    Int32 ->                                -- priority : TBasicType TInt32
    Int32 ->                                -- pid : TBasicType TInt32
    FunPtr ChildWatchFuncC ->               -- function : TInterface "GLib" "ChildWatchFunc"
    Ptr () ->                               -- data : TBasicType TVoid
    FunPtr DestroyNotifyC ->                -- notify : TInterface "GLib" "DestroyNotify"
    IO Word32


childWatchAdd ::
    (MonadIO m) =>
    Int32 ->                                -- priority
    Int32 ->                                -- pid
    ChildWatchFunc ->                       -- function
    m Word32
childWatchAdd priority pid function = liftIO $ do
    function' <- mkChildWatchFunc (childWatchFuncWrapper Nothing function)
    let data_ = castFunPtrToPtr function'
    let notify = safeFreeFunPtrPtr
    result <- g_child_watch_add_full priority pid function' data_ notify
    return result


-- function g_checksum_type_get_length
-- Args : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "checksum_type", argType = TInterface "GLib" "ChecksumType", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_checksum_type_get_length" g_checksum_type_get_length :: 
    CUInt ->                                -- checksum_type : TInterface "GLib" "ChecksumType"
    IO Int64


checksumTypeGetLength ::
    (MonadIO m) =>
    ChecksumType ->                         -- checksum_type
    m Int64
checksumTypeGetLength checksum_type = liftIO $ do
    let checksum_type' = (fromIntegral . fromEnum) checksum_type
    result <- g_checksum_type_get_length checksum_type'
    return result


-- function glib_check_version
-- Args : [Arg {argName = "required_major", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "required_minor", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "required_micro", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "required_major", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "required_minor", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "required_micro", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "glib_check_version" glib_check_version :: 
    Word32 ->                               -- required_major : TBasicType TUInt32
    Word32 ->                               -- required_minor : TBasicType TUInt32
    Word32 ->                               -- required_micro : TBasicType TUInt32
    IO CString


checkVersion ::
    (MonadIO m) =>
    Word32 ->                               -- required_major
    Word32 ->                               -- required_minor
    Word32 ->                               -- required_micro
    m T.Text
checkVersion required_major required_minor required_micro = liftIO $ do
    result <- glib_check_version required_major required_minor required_micro
    checkUnexpectedReturnNULL "glib_check_version" result
    result' <- cstringToText result
    return result'


-- function g_chdir
-- Args : [Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "path", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_chdir" g_chdir :: 
    CString ->                              -- path : TBasicType TUTF8
    IO Int32


chdir ::
    (MonadIO m) =>
    T.Text ->                               -- path
    m Int32
chdir path = liftIO $ do
    path' <- textToCString path
    result <- g_chdir path'
    freeMem path'
    return result


-- function g_byte_array_unref
-- Args : [Arg {argName = "array", argType = TByteArray, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "array", argType = TByteArray, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_unref" g_byte_array_unref :: 
    Ptr GByteArray ->                       -- array : TByteArray
    IO ()


byteArrayUnref ::
    (MonadIO m) =>
    ByteString ->                           -- array
    m ()
byteArrayUnref array = liftIO $ do
    array' <- packGByteArray array
    g_byte_array_unref array'
    unrefGByteArray array'
    return ()


-- function g_byte_array_new_take
-- Args : [Arg {argName = "data", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "data", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- returnType : TByteArray
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_new_take" g_byte_array_new_take :: 
    Ptr Word8 ->                            -- data : TCArray False (-1) 1 (TBasicType TUInt8)
    Word64 ->                               -- len : TBasicType TUInt64
    IO (Ptr GByteArray)


byteArrayNewTake ::
    (MonadIO m) =>
    ByteString ->                           -- data
    m ByteString
byteArrayNewTake data_ = liftIO $ do
    let len = fromIntegral $ B.length data_
    data_' <- packByteString data_
    result <- g_byte_array_new_take data_' len
    checkUnexpectedReturnNULL "g_byte_array_new_take" result
    result' <- unpackGByteArray result
    unrefGByteArray result
    return result'


-- function g_byte_array_new
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TByteArray
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_new" g_byte_array_new :: 
    IO (Ptr GByteArray)


byteArrayNew ::
    (MonadIO m) =>
    m ByteString
byteArrayNew  = liftIO $ do
    result <- g_byte_array_new
    checkUnexpectedReturnNULL "g_byte_array_new" result
    result' <- unpackGByteArray result
    unrefGByteArray result
    return result'


-- function g_byte_array_free_to_bytes
-- Args : [Arg {argName = "array", argType = TByteArray, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "array", argType = TByteArray, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- returnType : TInterface "GLib" "Bytes"
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_free_to_bytes" g_byte_array_free_to_bytes :: 
    Ptr GByteArray ->                       -- array : TByteArray
    IO (Ptr Bytes)


byteArrayFreeToBytes ::
    (MonadIO m) =>
    ByteString ->                           -- array
    m Bytes
byteArrayFreeToBytes array = liftIO $ do
    array' <- packGByteArray array
    result <- g_byte_array_free_to_bytes array'
    checkUnexpectedReturnNULL "g_byte_array_free_to_bytes" result
    result' <- (wrapBoxed Bytes) result
    return result'


-- function g_byte_array_free
-- Args : [Arg {argName = "array", argType = TByteArray, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "free_segment", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "array", argType = TByteArray, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "free_segment", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt8
-- throws : False
-- Skip return : False

foreign import ccall "g_byte_array_free" g_byte_array_free :: 
    Ptr GByteArray ->                       -- array : TByteArray
    CInt ->                                 -- free_segment : TBasicType TBoolean
    IO Word8


byteArrayFree ::
    (MonadIO m) =>
    ByteString ->                           -- array
    Bool ->                                 -- free_segment
    m Word8
byteArrayFree array free_segment = liftIO $ do
    array' <- packGByteArray array
    let free_segment' = (fromIntegral . fromEnum) free_segment
    result <- g_byte_array_free array' free_segment'
    unrefGByteArray array'
    return result


-- function g_build_pathv
-- Args : [Arg {argName = "separator", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "args", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "separator", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "args", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_build_pathv" g_build_pathv :: 
    CString ->                              -- separator : TBasicType TUTF8
    Ptr CString ->                          -- args : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO CString


buildPathv ::
    (MonadIO m) =>
    T.Text ->                               -- separator
    [T.Text] ->                             -- args
    m T.Text
buildPathv separator args = liftIO $ do
    separator' <- textToCString separator
    args' <- packZeroTerminatedUTF8CArray args
    result <- g_build_pathv separator' args'
    checkUnexpectedReturnNULL "g_build_pathv" result
    result' <- cstringToText result
    freeMem result
    freeMem separator'
    mapZeroTerminatedCArray freeMem args'
    freeMem args'
    return result'


-- function g_build_filenamev
-- Args : [Arg {argName = "args", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "args", argType = TCArray True (-1) (-1) (TBasicType TUTF8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_build_filenamev" g_build_filenamev :: 
    Ptr CString ->                          -- args : TCArray True (-1) (-1) (TBasicType TUTF8)
    IO CString


buildFilenamev ::
    (MonadIO m) =>
    [T.Text] ->                             -- args
    m T.Text
buildFilenamev args = liftIO $ do
    args' <- packZeroTerminatedUTF8CArray args
    result <- g_build_filenamev args'
    checkUnexpectedReturnNULL "g_build_filenamev" result
    result' <- cstringToText result
    freeMem result
    mapZeroTerminatedCArray freeMem args'
    freeMem args'
    return result'


-- function g_bookmark_file_error_quark
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_bookmark_file_error_quark" g_bookmark_file_error_quark :: 
    IO Word32


bookmarkFileErrorQuark ::
    (MonadIO m) =>
    m Word32
bookmarkFileErrorQuark  = liftIO $ do
    result <- g_bookmark_file_error_quark
    return result


-- function g_bit_unlock
-- Args : [Arg {argName = "address", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "address", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_bit_unlock" g_bit_unlock :: 
    Int32 ->                                -- address : TBasicType TInt32
    Int32 ->                                -- lock_bit : TBasicType TInt32
    IO ()


bitUnlock ::
    (MonadIO m) =>
    Int32 ->                                -- address
    Int32 ->                                -- lock_bit
    m ()
bitUnlock address lock_bit = liftIO $ do
    g_bit_unlock address lock_bit
    return ()


-- function g_bit_trylock
-- Args : [Arg {argName = "address", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "address", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_bit_trylock" g_bit_trylock :: 
    Int32 ->                                -- address : TBasicType TInt32
    Int32 ->                                -- lock_bit : TBasicType TInt32
    IO CInt


bitTrylock ::
    (MonadIO m) =>
    Int32 ->                                -- address
    Int32 ->                                -- lock_bit
    m Bool
bitTrylock address lock_bit = liftIO $ do
    result <- g_bit_trylock address lock_bit
    let result' = (/= 0) result
    return result'


-- function g_bit_storage
-- Args : [Arg {argName = "number", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "number", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_bit_storage" g_bit_storage :: 
    Word64 ->                               -- number : TBasicType TUInt64
    IO Word32


bitStorage ::
    (MonadIO m) =>
    Word64 ->                               -- number
    m Word32
bitStorage number = liftIO $ do
    result <- g_bit_storage number
    return result


-- function g_bit_nth_msf
-- Args : [Arg {argName = "mask", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nth_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "mask", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nth_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_bit_nth_msf" g_bit_nth_msf :: 
    Word64 ->                               -- mask : TBasicType TUInt64
    Int32 ->                                -- nth_bit : TBasicType TInt32
    IO Int32


bitNthMsf ::
    (MonadIO m) =>
    Word64 ->                               -- mask
    Int32 ->                                -- nth_bit
    m Int32
bitNthMsf mask nth_bit = liftIO $ do
    result <- g_bit_nth_msf mask nth_bit
    return result


-- function g_bit_nth_lsf
-- Args : [Arg {argName = "mask", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nth_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "mask", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nth_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_bit_nth_lsf" g_bit_nth_lsf :: 
    Word64 ->                               -- mask : TBasicType TUInt64
    Int32 ->                                -- nth_bit : TBasicType TInt32
    IO Int32


bitNthLsf ::
    (MonadIO m) =>
    Word64 ->                               -- mask
    Int32 ->                                -- nth_bit
    m Int32
bitNthLsf mask nth_bit = liftIO $ do
    result <- g_bit_nth_lsf mask nth_bit
    return result


-- function g_bit_lock
-- Args : [Arg {argName = "address", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "address", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "lock_bit", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_bit_lock" g_bit_lock :: 
    Int32 ->                                -- address : TBasicType TInt32
    Int32 ->                                -- lock_bit : TBasicType TInt32
    IO ()


bitLock ::
    (MonadIO m) =>
    Int32 ->                                -- address
    Int32 ->                                -- lock_bit
    m ()
bitLock address lock_bit = liftIO $ do
    g_bit_lock address lock_bit
    return ()


-- function g_basename
-- Args : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "file_name", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_basename" g_basename :: 
    CString ->                              -- file_name : TBasicType TUTF8
    IO CString

{-# DEPRECATED basename ["(Since version 2.2)","Use g_path_get_basename() instead, but notice","    that g_path_get_basename() allocates new memory for the","    returned string, unlike this function which returns a pointer","    into the argument."]#-}
basename ::
    (MonadIO m) =>
    T.Text ->                               -- file_name
    m T.Text
basename file_name = liftIO $ do
    file_name' <- textToCString file_name
    result <- g_basename file_name'
    checkUnexpectedReturnNULL "g_basename" result
    result' <- cstringToText result
    freeMem file_name'
    return result'


-- function g_base64_encode
-- Args : [Arg {argName = "data", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "len", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "data", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_base64_encode" g_base64_encode :: 
    Ptr Word8 ->                            -- data : TCArray False (-1) 1 (TBasicType TUInt8)
    Word64 ->                               -- len : TBasicType TUInt64
    IO CString


base64Encode ::
    (MonadIO m) =>
    ByteString ->                           -- data
    m T.Text
base64Encode data_ = liftIO $ do
    let len = fromIntegral $ B.length data_
    data_' <- packByteString data_
    result <- g_base64_encode data_' len
    checkUnexpectedReturnNULL "g_base64_encode" result
    result' <- cstringToText result
    freeMem result
    freeMem data_'
    return result'


-- function g_base64_decode_inplace
-- Args : [Arg {argName = "text", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "out_len", argType = TBasicType TUInt64, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "out_len", argType = TBasicType TUInt64, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "text", argType = TCArray False (-1) 1 (TBasicType TUInt8), direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- returnType : TBasicType TUInt8
-- throws : False
-- Skip return : False

foreign import ccall "g_base64_decode_inplace" g_base64_decode_inplace :: 
    Ptr (Ptr Word8) ->                      -- text : TCArray False (-1) 1 (TBasicType TUInt8)
    Ptr Word64 ->                           -- out_len : TBasicType TUInt64
    IO Word8


base64DecodeInplace ::
    (MonadIO m) =>
    ByteString ->                           -- text
    m (Word8,ByteString)
base64DecodeInplace text = liftIO $ do
    let out_len = fromIntegral $ B.length text
    text' <- packByteString text
    text'' <- allocMem :: IO (Ptr (Ptr Word8))
    poke text'' text'
    out_len' <- allocMem :: IO (Ptr Word64)
    poke out_len' out_len
    result <- g_base64_decode_inplace text'' out_len'
    out_len'' <- peek out_len'
    text''' <- peek text''
    text'''' <- (unpackByteStringWithLength out_len'') text'''
    freeMem text'''
    freeMem text''
    freeMem out_len'
    return (result, text'''')


-- function g_base64_decode
-- Args : [Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "out_len", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : [Arg {argName = "out_len", argType = TBasicType TUInt64, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- hInArgs : [Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TCArray False (-1) 1 (TBasicType TUInt8)
-- throws : False
-- Skip return : False

foreign import ccall "g_base64_decode" g_base64_decode :: 
    CString ->                              -- text : TBasicType TUTF8
    Ptr Word64 ->                           -- out_len : TBasicType TUInt64
    IO (Ptr Word8)


base64Decode ::
    (MonadIO m) =>
    T.Text ->                               -- text
    m ByteString
base64Decode text = liftIO $ do
    text' <- textToCString text
    out_len <- allocMem :: IO (Ptr Word64)
    result <- g_base64_decode text' out_len
    out_len' <- peek out_len
    checkUnexpectedReturnNULL "g_base64_decode" result
    result' <- (unpackByteStringWithLength out_len') result
    freeMem result
    freeMem text'
    freeMem out_len
    return result'


-- function g_atomic_pointer_xor
-- Args : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_pointer_xor" g_atomic_pointer_xor :: 
    Ptr () ->                               -- atomic : TBasicType TVoid
    Word64 ->                               -- val : TBasicType TUInt64
    IO Word64


atomicPointerXor ::
    (MonadIO m) =>
    Ptr () ->                               -- atomic
    Word64 ->                               -- val
    m Word64
atomicPointerXor atomic val = liftIO $ do
    result <- g_atomic_pointer_xor atomic val
    return result


-- function g_atomic_pointer_set
-- Args : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_pointer_set" g_atomic_pointer_set :: 
    Ptr () ->                               -- atomic : TBasicType TVoid
    Ptr () ->                               -- newval : TBasicType TVoid
    IO ()


atomicPointerSet ::
    (MonadIO m) =>
    Ptr () ->                               -- atomic
    Ptr () ->                               -- newval
    m ()
atomicPointerSet atomic newval = liftIO $ do
    g_atomic_pointer_set atomic newval
    return ()


-- function g_atomic_pointer_or
-- Args : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_pointer_or" g_atomic_pointer_or :: 
    Ptr () ->                               -- atomic : TBasicType TVoid
    Word64 ->                               -- val : TBasicType TUInt64
    IO Word64


atomicPointerOr ::
    (MonadIO m) =>
    Ptr () ->                               -- atomic
    Word64 ->                               -- val
    m Word64
atomicPointerOr atomic val = liftIO $ do
    result <- g_atomic_pointer_or atomic val
    return result


-- function g_atomic_pointer_compare_and_exchange
-- Args : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "oldval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "oldval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_pointer_compare_and_exchange" g_atomic_pointer_compare_and_exchange :: 
    Ptr () ->                               -- atomic : TBasicType TVoid
    Ptr () ->                               -- oldval : TBasicType TVoid
    Ptr () ->                               -- newval : TBasicType TVoid
    IO CInt


atomicPointerCompareAndExchange ::
    (MonadIO m) =>
    Ptr () ->                               -- atomic
    Ptr () ->                               -- oldval
    Ptr () ->                               -- newval
    m Bool
atomicPointerCompareAndExchange atomic oldval newval = liftIO $ do
    result <- g_atomic_pointer_compare_and_exchange atomic oldval newval
    let result' = (/= 0) result
    return result'


-- function g_atomic_pointer_and
-- Args : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_pointer_and" g_atomic_pointer_and :: 
    Ptr () ->                               -- atomic : TBasicType TVoid
    Word64 ->                               -- val : TBasicType TUInt64
    IO Word64


atomicPointerAnd ::
    (MonadIO m) =>
    Ptr () ->                               -- atomic
    Word64 ->                               -- val
    m Word64
atomicPointerAnd atomic val = liftIO $ do
    result <- g_atomic_pointer_and atomic val
    return result


-- function g_atomic_pointer_add
-- Args : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_pointer_add" g_atomic_pointer_add :: 
    Ptr () ->                               -- atomic : TBasicType TVoid
    Int64 ->                                -- val : TBasicType TInt64
    IO Int64


atomicPointerAdd ::
    (MonadIO m) =>
    Ptr () ->                               -- atomic
    Int64 ->                                -- val
    m Int64
atomicPointerAdd atomic val = liftIO $ do
    result <- g_atomic_pointer_add atomic val
    return result


-- function g_atomic_int_xor
-- Args : [Arg {argName = "atomic", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_xor" g_atomic_int_xor :: 
    Word32 ->                               -- atomic : TBasicType TUInt32
    Word32 ->                               -- val : TBasicType TUInt32
    IO Word32


atomicIntXor ::
    (MonadIO m) =>
    Word32 ->                               -- atomic
    Word32 ->                               -- val
    m Word32
atomicIntXor atomic val = liftIO $ do
    result <- g_atomic_int_xor atomic val
    return result


-- function g_atomic_int_set
-- Args : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_set" g_atomic_int_set :: 
    Int32 ->                                -- atomic : TBasicType TInt32
    Int32 ->                                -- newval : TBasicType TInt32
    IO ()


atomicIntSet ::
    (MonadIO m) =>
    Int32 ->                                -- atomic
    Int32 ->                                -- newval
    m ()
atomicIntSet atomic newval = liftIO $ do
    g_atomic_int_set atomic newval
    return ()


-- function g_atomic_int_or
-- Args : [Arg {argName = "atomic", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_or" g_atomic_int_or :: 
    Word32 ->                               -- atomic : TBasicType TUInt32
    Word32 ->                               -- val : TBasicType TUInt32
    IO Word32


atomicIntOr ::
    (MonadIO m) =>
    Word32 ->                               -- atomic
    Word32 ->                               -- val
    m Word32
atomicIntOr atomic val = liftIO $ do
    result <- g_atomic_int_or atomic val
    return result


-- function g_atomic_int_inc
-- Args : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_inc" g_atomic_int_inc :: 
    Int32 ->                                -- atomic : TBasicType TInt32
    IO ()


atomicIntInc ::
    (MonadIO m) =>
    Int32 ->                                -- atomic
    m ()
atomicIntInc atomic = liftIO $ do
    g_atomic_int_inc atomic
    return ()


-- function g_atomic_int_get
-- Args : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_get" g_atomic_int_get :: 
    Int32 ->                                -- atomic : TBasicType TInt32
    IO Int32


atomicIntGet ::
    (MonadIO m) =>
    Int32 ->                                -- atomic
    m Int32
atomicIntGet atomic = liftIO $ do
    result <- g_atomic_int_get atomic
    return result


-- function g_atomic_int_exchange_and_add
-- Args : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_exchange_and_add" g_atomic_int_exchange_and_add :: 
    Int32 ->                                -- atomic : TBasicType TInt32
    Int32 ->                                -- val : TBasicType TInt32
    IO Int32

{-# DEPRECATED atomicIntExchangeAndAdd ["(Since version 2.30)","Use g_atomic_int_add() instead."]#-}
atomicIntExchangeAndAdd ::
    (MonadIO m) =>
    Int32 ->                                -- atomic
    Int32 ->                                -- val
    m Int32
atomicIntExchangeAndAdd atomic val = liftIO $ do
    result <- g_atomic_int_exchange_and_add atomic val
    return result


-- function g_atomic_int_dec_and_test
-- Args : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_dec_and_test" g_atomic_int_dec_and_test :: 
    Int32 ->                                -- atomic : TBasicType TInt32
    IO CInt


atomicIntDecAndTest ::
    (MonadIO m) =>
    Int32 ->                                -- atomic
    m Bool
atomicIntDecAndTest atomic = liftIO $ do
    result <- g_atomic_int_dec_and_test atomic
    let result' = (/= 0) result
    return result'


-- function g_atomic_int_compare_and_exchange
-- Args : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "oldval", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "oldval", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "newval", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_compare_and_exchange" g_atomic_int_compare_and_exchange :: 
    Int32 ->                                -- atomic : TBasicType TInt32
    Int32 ->                                -- oldval : TBasicType TInt32
    Int32 ->                                -- newval : TBasicType TInt32
    IO CInt


atomicIntCompareAndExchange ::
    (MonadIO m) =>
    Int32 ->                                -- atomic
    Int32 ->                                -- oldval
    Int32 ->                                -- newval
    m Bool
atomicIntCompareAndExchange atomic oldval newval = liftIO $ do
    result <- g_atomic_int_compare_and_exchange atomic oldval newval
    let result' = (/= 0) result
    return result'


-- function g_atomic_int_and
-- Args : [Arg {argName = "atomic", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_and" g_atomic_int_and :: 
    Word32 ->                               -- atomic : TBasicType TUInt32
    Word32 ->                               -- val : TBasicType TUInt32
    IO Word32


atomicIntAnd ::
    (MonadIO m) =>
    Word32 ->                               -- atomic
    Word32 ->                               -- val
    m Word32
atomicIntAnd atomic val = liftIO $ do
    result <- g_atomic_int_and atomic val
    return result


-- function g_atomic_int_add
-- Args : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "atomic", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "val", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_atomic_int_add" g_atomic_int_add :: 
    Int32 ->                                -- atomic : TBasicType TInt32
    Int32 ->                                -- val : TBasicType TInt32
    IO Int32


atomicIntAdd ::
    (MonadIO m) =>
    Int32 ->                                -- atomic
    Int32 ->                                -- val
    m Int32
atomicIntAdd atomic val = liftIO $ do
    result <- g_atomic_int_add atomic val
    return result


-- function g_atexit
-- Args : [Arg {argName = "func", argType = TInterface "GLib" "VoidFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "func", argType = TInterface "GLib" "VoidFunc", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeAsync, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_atexit" g_atexit :: 
    FunPtr VoidFuncC ->                     -- func : TInterface "GLib" "VoidFunc"
    IO ()

{-# DEPRECATED atexit ["(Since version 2.32)","It is best to avoid g_atexit()."]#-}
atexit ::
    (MonadIO m) =>
    VoidFunc ->                             -- func
    m ()
atexit func = liftIO $ do
    ptrfunc <- callocMem :: IO (Ptr (FunPtr VoidFuncC))
    func' <- mkVoidFunc (voidFuncWrapper (Just ptrfunc) func)
    poke ptrfunc func'
    g_atexit func'
    return ()


-- function g_assertion_message_expr
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_assertion_message_expr" g_assertion_message_expr :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- file : TBasicType TUTF8
    Int32 ->                                -- line : TBasicType TInt32
    CString ->                              -- func : TBasicType TUTF8
    CString ->                              -- expr : TBasicType TUTF8
    IO ()


assertionMessageExpr ::
    (MonadIO m) =>
    T.Text ->                               -- domain
    T.Text ->                               -- file
    Int32 ->                                -- line
    T.Text ->                               -- func
    T.Text ->                               -- expr
    m ()
assertionMessageExpr domain file line func expr = liftIO $ do
    domain' <- textToCString domain
    file' <- textToCString file
    func' <- textToCString func
    expr' <- textToCString expr
    g_assertion_message_expr domain' file' line func' expr'
    freeMem domain'
    freeMem file'
    freeMem func'
    freeMem expr'
    return ()


-- function g_assertion_message_error
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "error", argType = TError, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "error_domain", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "error_code", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "error", argType = TError, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "error_domain", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "error_code", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_assertion_message_error" g_assertion_message_error :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- file : TBasicType TUTF8
    Int32 ->                                -- line : TBasicType TInt32
    CString ->                              -- func : TBasicType TUTF8
    CString ->                              -- expr : TBasicType TUTF8
    Ptr GError ->                           -- error : TError
    Word32 ->                               -- error_domain : TBasicType TUInt32
    Int32 ->                                -- error_code : TBasicType TInt32
    IO ()


assertionMessageError ::
    (MonadIO m) =>
    T.Text ->                               -- domain
    T.Text ->                               -- file
    Int32 ->                                -- line
    T.Text ->                               -- func
    T.Text ->                               -- expr
    GError ->                               -- error
    Word32 ->                               -- error_domain
    Int32 ->                                -- error_code
    m ()
assertionMessageError domain file line func expr error_ error_domain error_code = liftIO $ do
    domain' <- textToCString domain
    file' <- textToCString file
    func' <- textToCString func
    expr' <- textToCString expr
    let error_' = unsafeManagedPtrGetPtr error_
    g_assertion_message_error domain' file' line func' expr' error_' error_domain error_code
    touchManagedPtr error_
    freeMem domain'
    freeMem file'
    freeMem func'
    freeMem expr'
    return ()


-- function g_assertion_message_cmpstr
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "arg1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cmp", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "arg2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "arg1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cmp", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "arg2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_assertion_message_cmpstr" g_assertion_message_cmpstr :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- file : TBasicType TUTF8
    Int32 ->                                -- line : TBasicType TInt32
    CString ->                              -- func : TBasicType TUTF8
    CString ->                              -- expr : TBasicType TUTF8
    CString ->                              -- arg1 : TBasicType TUTF8
    CString ->                              -- cmp : TBasicType TUTF8
    CString ->                              -- arg2 : TBasicType TUTF8
    IO ()


assertionMessageCmpstr ::
    (MonadIO m) =>
    T.Text ->                               -- domain
    T.Text ->                               -- file
    Int32 ->                                -- line
    T.Text ->                               -- func
    T.Text ->                               -- expr
    T.Text ->                               -- arg1
    T.Text ->                               -- cmp
    T.Text ->                               -- arg2
    m ()
assertionMessageCmpstr domain file line func expr arg1 cmp arg2 = liftIO $ do
    domain' <- textToCString domain
    file' <- textToCString file
    func' <- textToCString func
    expr' <- textToCString expr
    arg1' <- textToCString arg1
    cmp' <- textToCString cmp
    arg2' <- textToCString arg2
    g_assertion_message_cmpstr domain' file' line func' expr' arg1' cmp' arg2'
    freeMem domain'
    freeMem file'
    freeMem func'
    freeMem expr'
    freeMem arg1'
    freeMem cmp'
    freeMem arg2'
    return ()


-- function g_assertion_message
-- Args : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "message", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "func", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "message", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_assertion_message" g_assertion_message :: 
    CString ->                              -- domain : TBasicType TUTF8
    CString ->                              -- file : TBasicType TUTF8
    Int32 ->                                -- line : TBasicType TInt32
    CString ->                              -- func : TBasicType TUTF8
    CString ->                              -- message : TBasicType TUTF8
    IO ()


assertionMessage ::
    (MonadIO m) =>
    T.Text ->                               -- domain
    T.Text ->                               -- file
    Int32 ->                                -- line
    T.Text ->                               -- func
    T.Text ->                               -- message
    m ()
assertionMessage domain file line func message = liftIO $ do
    domain' <- textToCString domain
    file' <- textToCString file
    func' <- textToCString func
    message' <- textToCString message
    g_assertion_message domain' file' line func' message'
    freeMem domain'
    freeMem file'
    freeMem func'
    freeMem message'
    return ()


-- function g_assert_warning
-- Args : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pretty_function", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expression", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "log_domain", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "file", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "line", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pretty_function", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "expression", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "g_assert_warning" g_assert_warning :: 
    CString ->                              -- log_domain : TBasicType TUTF8
    CString ->                              -- file : TBasicType TUTF8
    Int32 ->                                -- line : TBasicType TInt32
    CString ->                              -- pretty_function : TBasicType TUTF8
    CString ->                              -- expression : TBasicType TUTF8
    IO ()


assertWarning ::
    (MonadIO m) =>
    T.Text ->                               -- log_domain
    T.Text ->                               -- file
    Int32 ->                                -- line
    T.Text ->                               -- pretty_function
    T.Text ->                               -- expression
    m ()
assertWarning log_domain file line pretty_function expression = liftIO $ do
    log_domain' <- textToCString log_domain
    file' <- textToCString file
    pretty_function' <- textToCString pretty_function
    expression' <- textToCString expression
    g_assert_warning log_domain' file' line pretty_function' expression'
    freeMem log_domain'
    freeMem file'
    freeMem pretty_function'
    freeMem expression'
    return ()


-- function g_ascii_xdigit_value
-- Args : [Arg {argName = "c", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_xdigit_value" g_ascii_xdigit_value :: 
    Int8 ->                                 -- c : TBasicType TInt8
    IO Int32


asciiXdigitValue ::
    (MonadIO m) =>
    Int8 ->                                 -- c
    m Int32
asciiXdigitValue c = liftIO $ do
    result <- g_ascii_xdigit_value c
    return result


-- function g_ascii_toupper
-- Args : [Arg {argName = "c", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt8
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_toupper" g_ascii_toupper :: 
    Int8 ->                                 -- c : TBasicType TInt8
    IO Int8


asciiToupper ::
    (MonadIO m) =>
    Int8 ->                                 -- c
    m Int8
asciiToupper c = liftIO $ do
    result <- g_ascii_toupper c
    return result


-- function g_ascii_tolower
-- Args : [Arg {argName = "c", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt8
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_tolower" g_ascii_tolower :: 
    Int8 ->                                 -- c : TBasicType TInt8
    IO Int8


asciiTolower ::
    (MonadIO m) =>
    Int8 ->                                 -- c
    m Int8
asciiTolower c = liftIO $ do
    result <- g_ascii_tolower c
    return result


-- function g_ascii_strup
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_strup" g_ascii_strup :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO CString


asciiStrup ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    m T.Text
asciiStrup str len = liftIO $ do
    str' <- textToCString str
    result <- g_ascii_strup str' len
    checkUnexpectedReturnNULL "g_ascii_strup" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_ascii_strtoull
-- Args : [Arg {argName = "nptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "nptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_strtoull" g_ascii_strtoull :: 
    CString ->                              -- nptr : TBasicType TUTF8
    CString ->                              -- endptr : TBasicType TUTF8
    Word32 ->                               -- base : TBasicType TUInt32
    IO Word64


asciiStrtoull ::
    (MonadIO m) =>
    T.Text ->                               -- nptr
    T.Text ->                               -- endptr
    Word32 ->                               -- base
    m Word64
asciiStrtoull nptr endptr base = liftIO $ do
    nptr' <- textToCString nptr
    endptr' <- textToCString endptr
    result <- g_ascii_strtoull nptr' endptr' base
    freeMem nptr'
    freeMem endptr'
    return result


-- function g_ascii_strtoll
-- Args : [Arg {argName = "nptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "nptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base", argType = TBasicType TUInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt64
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_strtoll" g_ascii_strtoll :: 
    CString ->                              -- nptr : TBasicType TUTF8
    CString ->                              -- endptr : TBasicType TUTF8
    Word32 ->                               -- base : TBasicType TUInt32
    IO Int64


asciiStrtoll ::
    (MonadIO m) =>
    T.Text ->                               -- nptr
    T.Text ->                               -- endptr
    Word32 ->                               -- base
    m Int64
asciiStrtoll nptr endptr base = liftIO $ do
    nptr' <- textToCString nptr
    endptr' <- textToCString endptr
    result <- g_ascii_strtoll nptr' endptr' base
    freeMem nptr'
    freeMem endptr'
    return result


-- function g_ascii_strtod
-- Args : [Arg {argName = "nptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "nptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "endptr", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TDouble
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_strtod" g_ascii_strtod :: 
    CString ->                              -- nptr : TBasicType TUTF8
    CString ->                              -- endptr : TBasicType TUTF8
    IO CDouble


asciiStrtod ::
    (MonadIO m) =>
    T.Text ->                               -- nptr
    T.Text ->                               -- endptr
    m Double
asciiStrtod nptr endptr = liftIO $ do
    nptr' <- textToCString nptr
    endptr' <- textToCString endptr
    result <- g_ascii_strtod nptr' endptr'
    let result' = realToFrac result
    freeMem nptr'
    freeMem endptr'
    return result'


-- function g_ascii_strncasecmp
-- Args : [Arg {argName = "s1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "s2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "s1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "s2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "n", argType = TBasicType TUInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_strncasecmp" g_ascii_strncasecmp :: 
    CString ->                              -- s1 : TBasicType TUTF8
    CString ->                              -- s2 : TBasicType TUTF8
    Word64 ->                               -- n : TBasicType TUInt64
    IO Int32


asciiStrncasecmp ::
    (MonadIO m) =>
    T.Text ->                               -- s1
    T.Text ->                               -- s2
    Word64 ->                               -- n
    m Int32
asciiStrncasecmp s1 s2 n = liftIO $ do
    s1' <- textToCString s1
    s2' <- textToCString s2
    result <- g_ascii_strncasecmp s1' s2' n
    freeMem s1'
    freeMem s2'
    return result


-- function g_ascii_strdown
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "len", argType = TBasicType TInt64, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_strdown" g_ascii_strdown :: 
    CString ->                              -- str : TBasicType TUTF8
    Int64 ->                                -- len : TBasicType TInt64
    IO CString


asciiStrdown ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Int64 ->                                -- len
    m T.Text
asciiStrdown str len = liftIO $ do
    str' <- textToCString str
    result <- g_ascii_strdown str' len
    checkUnexpectedReturnNULL "g_ascii_strdown" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function g_ascii_strcasecmp
-- Args : [Arg {argName = "s1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "s2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "s1", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "s2", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_strcasecmp" g_ascii_strcasecmp :: 
    CString ->                              -- s1 : TBasicType TUTF8
    CString ->                              -- s2 : TBasicType TUTF8
    IO Int32


asciiStrcasecmp ::
    (MonadIO m) =>
    T.Text ->                               -- s1
    T.Text ->                               -- s2
    m Int32
asciiStrcasecmp s1 s2 = liftIO $ do
    s1' <- textToCString s1
    s2' <- textToCString s2
    result <- g_ascii_strcasecmp s1' s2'
    freeMem s1'
    freeMem s2'
    return result


-- function g_ascii_formatd
-- Args : [Arg {argName = "buffer", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buf_len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "format", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "d", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "buffer", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buf_len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "format", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "d", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_formatd" g_ascii_formatd :: 
    CString ->                              -- buffer : TBasicType TUTF8
    Int32 ->                                -- buf_len : TBasicType TInt32
    CString ->                              -- format : TBasicType TUTF8
    CDouble ->                              -- d : TBasicType TDouble
    IO CString


asciiFormatd ::
    (MonadIO m) =>
    T.Text ->                               -- buffer
    Int32 ->                                -- buf_len
    T.Text ->                               -- format
    Double ->                               -- d
    m T.Text
asciiFormatd buffer buf_len format d = liftIO $ do
    buffer' <- textToCString buffer
    format' <- textToCString format
    let d' = realToFrac d
    result <- g_ascii_formatd buffer' buf_len format' d'
    checkUnexpectedReturnNULL "g_ascii_formatd" result
    result' <- cstringToText result
    freeMem result
    freeMem buffer'
    freeMem format'
    return result'


-- function g_ascii_dtostr
-- Args : [Arg {argName = "buffer", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buf_len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "d", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "buffer", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "buf_len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "d", argType = TBasicType TDouble, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_dtostr" g_ascii_dtostr :: 
    CString ->                              -- buffer : TBasicType TUTF8
    Int32 ->                                -- buf_len : TBasicType TInt32
    CDouble ->                              -- d : TBasicType TDouble
    IO CString


asciiDtostr ::
    (MonadIO m) =>
    T.Text ->                               -- buffer
    Int32 ->                                -- buf_len
    Double ->                               -- d
    m T.Text
asciiDtostr buffer buf_len d = liftIO $ do
    buffer' <- textToCString buffer
    let d' = realToFrac d
    result <- g_ascii_dtostr buffer' buf_len d'
    checkUnexpectedReturnNULL "g_ascii_dtostr" result
    result' <- cstringToText result
    freeMem result
    freeMem buffer'
    return result'


-- function g_ascii_digit_value
-- Args : [Arg {argName = "c", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "c", argType = TBasicType TInt8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_ascii_digit_value" g_ascii_digit_value :: 
    Int8 ->                                 -- c : TBasicType TInt8
    IO Int32


asciiDigitValue ::
    (MonadIO m) =>
    Int8 ->                                 -- c
    m Int32
asciiDigitValue c = liftIO $ do
    result <- g_ascii_digit_value c
    return result


-- function g_access
-- Args : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "filename", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "mode", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "g_access" g_access :: 
    CString ->                              -- filename : TBasicType TUTF8
    Int32 ->                                -- mode : TBasicType TInt32
    IO Int32


access ::
    (MonadIO m) =>
    T.Text ->                               -- filename
    Int32 ->                                -- mode
    m Int32
access filename mode = liftIO $ do
    filename' <- textToCString filename
    result <- g_access filename' mode
    freeMem filename'
    return result