{- |
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.Pango.Functions
    ( 

 -- * Methods
-- ** attrTypeGetName
    attrTypeGetName                         ,


-- ** attrTypeRegister
    attrTypeRegister                        ,


-- ** bidiTypeForUnichar
    bidiTypeForUnichar                      ,


-- ** break
    break                                   ,


-- ** configKeyGet
    configKeyGet                            ,


-- ** configKeyGetSystem
    configKeyGetSystem                      ,


-- ** defaultBreak
    defaultBreak                            ,


-- ** extentsToPixels
    extentsToPixels                         ,


-- ** findBaseDir
    findBaseDir                             ,


-- ** findParagraphBoundary
    findParagraphBoundary                   ,


-- ** fontDescriptionFromString
    fontDescriptionFromString               ,


-- ** getLibSubdirectory
    getLibSubdirectory                      ,


-- ** getLogAttrs
    getLogAttrs                             ,


-- ** getMirrorChar
    getMirrorChar                           ,


-- ** getSysconfSubdirectory
    getSysconfSubdirectory                  ,


-- ** gravityGetForMatrix
    gravityGetForMatrix                     ,


-- ** gravityGetForScript
    gravityGetForScript                     ,


-- ** gravityGetForScriptAndWidth
    gravityGetForScriptAndWidth             ,


-- ** gravityToRotation
    gravityToRotation                       ,


-- ** isZeroWidth
    isZeroWidth                             ,


-- ** itemize
    itemize                                 ,


-- ** itemizeWithBaseDir
    itemizeWithBaseDir                      ,


-- ** languageFromString
    languageFromString                      ,


-- ** languageGetDefault
    languageGetDefault                      ,


-- ** log2visGetEmbeddingLevels
    log2visGetEmbeddingLevels               ,


-- ** lookupAliases
    lookupAliases                           ,


-- ** markupParserFinish
    markupParserFinish                      ,


-- ** markupParserNew
    markupParserNew                         ,


-- ** moduleRegister
    moduleRegister                          ,


-- ** parseEnum
    parseEnum                               ,


-- ** parseMarkup
    parseMarkup                             ,


-- ** parseStretch
    parseStretch                            ,


-- ** parseStyle
    parseStyle                              ,


-- ** parseVariant
    parseVariant                            ,


-- ** parseWeight
    parseWeight                             ,


-- ** quantizeLineGeometry
    quantizeLineGeometry                    ,


-- ** readLine
    readLine                                ,


-- ** reorderItems
    reorderItems                            ,


-- ** scanInt
    scanInt                                 ,


-- ** scanString
    scanString                              ,


-- ** scanWord
    scanWord                                ,


-- ** scriptForUnichar
    scriptForUnichar                        ,


-- ** scriptGetSampleLanguage
    scriptGetSampleLanguage                 ,


-- ** shape
    shape                                   ,


-- ** shapeFull
    shapeFull                               ,


-- ** skipSpace
    skipSpace                               ,


-- ** splitFileList
    splitFileList                           ,


-- ** trimString
    trimString                              ,


-- ** unicharDirection
    unicharDirection                        ,


-- ** unitsFromDouble
    unitsFromDouble                         ,


-- ** unitsToDouble
    unitsToDouble                           ,


-- ** version
    version                                 ,


-- ** versionCheck
    versionCheck                            ,


-- ** versionString
    versionString                           ,




    ) 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.Pango.Types
import GI.Pango.Callbacks
import qualified GI.GLib as GLib

-- function pango_version_string
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "pango_version_string" pango_version_string :: 
    IO CString


versionString ::
    (MonadIO m) =>
    m T.Text
versionString  = liftIO $ do
    result <- pango_version_string
    checkUnexpectedReturnNULL "pango_version_string" result
    result' <- cstringToText result
    return result'


-- function pango_version_check
-- Args : [Arg {argName = "required_major", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "required_minor", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "required_micro", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "required_major", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "required_minor", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "required_micro", 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 "pango_version_check" pango_version_check :: 
    Int32 ->                                -- required_major : TBasicType TInt32
    Int32 ->                                -- required_minor : TBasicType TInt32
    Int32 ->                                -- required_micro : TBasicType TInt32
    IO CString


versionCheck ::
    (MonadIO m) =>
    Int32 ->                                -- required_major
    Int32 ->                                -- required_minor
    Int32 ->                                -- required_micro
    m T.Text
versionCheck required_major required_minor required_micro = liftIO $ do
    result <- pango_version_check required_major required_minor required_micro
    checkUnexpectedReturnNULL "pango_version_check" result
    result' <- cstringToText result
    return result'


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

foreign import ccall "pango_version" pango_version :: 
    IO Int32


version ::
    (MonadIO m) =>
    m Int32
version  = liftIO $ do
    result <- pango_version
    return result


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

foreign import ccall "pango_units_to_double" pango_units_to_double :: 
    Int32 ->                                -- i : TBasicType TInt32
    IO CDouble


unitsToDouble ::
    (MonadIO m) =>
    Int32 ->                                -- i
    m Double
unitsToDouble i = liftIO $ do
    result <- pango_units_to_double i
    let result' = realToFrac result
    return result'


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

foreign import ccall "pango_units_from_double" pango_units_from_double :: 
    CDouble ->                              -- d : TBasicType TDouble
    IO Int32


unitsFromDouble ::
    (MonadIO m) =>
    Double ->                               -- d
    m Int32
unitsFromDouble d = liftIO $ do
    let d' = realToFrac d
    result <- pango_units_from_double d'
    return result


-- function pango_unichar_direction
-- 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 "Pango" "Direction"
-- throws : False
-- Skip return : False

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


unicharDirection ::
    (MonadIO m) =>
    Char ->                                 -- ch
    m Direction
unicharDirection ch = liftIO $ do
    let ch' = (fromIntegral . ord) ch
    result <- pango_unichar_direction ch'
    let result' = (toEnum . fromIntegral) result
    return result'


-- function pango_trim_string
-- 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 "pango_trim_string" pango_trim_string :: 
    CString ->                              -- str : TBasicType TUTF8
    IO CString

{-# DEPRECATED trimString ["(Since version 1.38)"]#-}
trimString ::
    (MonadIO m) =>
    T.Text ->                               -- str
    m T.Text
trimString str = liftIO $ do
    str' <- textToCString str
    result <- pango_trim_string str'
    checkUnexpectedReturnNULL "pango_trim_string" result
    result' <- cstringToText result
    freeMem result
    freeMem str'
    return result'


-- function pango_split_file_list
-- 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 : TCArray True (-1) (-1) (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "pango_split_file_list" pango_split_file_list :: 
    CString ->                              -- str : TBasicType TUTF8
    IO (Ptr CString)

{-# DEPRECATED splitFileList ["(Since version 1.38)"]#-}
splitFileList ::
    (MonadIO m) =>
    T.Text ->                               -- str
    m [T.Text]
splitFileList str = liftIO $ do
    str' <- textToCString str
    result <- pango_split_file_list str'
    checkUnexpectedReturnNULL "pango_split_file_list" result
    result' <- unpackZeroTerminatedUTF8CArray result
    mapZeroTerminatedCArray freeMem result
    freeMem result
    freeMem str'
    return result'


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

foreign import ccall "pango_skip_space" pango_skip_space :: 
    Ptr CString ->                          -- pos : TBasicType TUTF8
    IO CInt

{-# DEPRECATED skipSpace ["(Since version 1.38)"]#-}
skipSpace ::
    (MonadIO m) =>
    T.Text ->                               -- pos
    m (Bool,T.Text)
skipSpace pos = liftIO $ do
    pos' <- textToCString pos
    pos'' <- allocMem :: IO (Ptr CString)
    poke pos'' pos'
    result <- pango_skip_space pos''
    let result' = (/= 0) result
    pos''' <- peek pos''
    pos'''' <- cstringToText pos'''
    freeMem pos'''
    freeMem pos''
    return (result', pos'''')


-- function pango_shape_full
-- Args : [Arg {argName = "item_text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "item_length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "paragraph_text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "paragraph_length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "analysis", argType = TInterface "Pango" "Analysis", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "glyphs", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "item_text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "item_length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "paragraph_text", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "paragraph_length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "analysis", argType = TInterface "Pango" "Analysis", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "glyphs", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_shape_full" pango_shape_full :: 
    CString ->                              -- item_text : TBasicType TUTF8
    Int32 ->                                -- item_length : TBasicType TInt32
    CString ->                              -- paragraph_text : TBasicType TUTF8
    Int32 ->                                -- paragraph_length : TBasicType TInt32
    Ptr Analysis ->                         -- analysis : TInterface "Pango" "Analysis"
    Ptr GlyphString ->                      -- glyphs : TInterface "Pango" "GlyphString"
    IO ()


shapeFull ::
    (MonadIO m) =>
    T.Text ->                               -- item_text
    Int32 ->                                -- item_length
    Maybe (T.Text) ->                       -- paragraph_text
    Int32 ->                                -- paragraph_length
    Analysis ->                             -- analysis
    GlyphString ->                          -- glyphs
    m ()
shapeFull item_text item_length paragraph_text paragraph_length analysis glyphs = liftIO $ do
    item_text' <- textToCString item_text
    maybeParagraph_text <- case paragraph_text of
        Nothing -> return nullPtr
        Just jParagraph_text -> do
            jParagraph_text' <- textToCString jParagraph_text
            return jParagraph_text'
    let analysis' = unsafeManagedPtrGetPtr analysis
    let glyphs' = unsafeManagedPtrGetPtr glyphs
    pango_shape_full item_text' item_length maybeParagraph_text paragraph_length analysis' glyphs'
    touchManagedPtr analysis
    touchManagedPtr glyphs
    freeMem item_text'
    freeMem maybeParagraph_text
    return ()


-- function pango_shape
-- Args : [Arg {argName = "text", 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},Arg {argName = "analysis", argType = TInterface "Pango" "Analysis", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "glyphs", argType = TInterface "Pango" "GlyphString", 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 TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "analysis", argType = TInterface "Pango" "Analysis", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "glyphs", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_shape" pango_shape :: 
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    Ptr Analysis ->                         -- analysis : TInterface "Pango" "Analysis"
    Ptr GlyphString ->                      -- glyphs : TInterface "Pango" "GlyphString"
    IO ()


shape ::
    (MonadIO m) =>
    T.Text ->                               -- text
    Int32 ->                                -- length
    Analysis ->                             -- analysis
    GlyphString ->                          -- glyphs
    m ()
shape text length_ analysis glyphs = liftIO $ do
    text' <- textToCString text
    let analysis' = unsafeManagedPtrGetPtr analysis
    let glyphs' = unsafeManagedPtrGetPtr glyphs
    pango_shape text' length_ analysis' glyphs'
    touchManagedPtr analysis
    touchManagedPtr glyphs
    freeMem text'
    return ()


-- function pango_script_get_sample_language
-- Args : [Arg {argName = "script", argType = TInterface "Pango" "Script", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "script", argType = TInterface "Pango" "Script", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Pango" "Language"
-- throws : False
-- Skip return : False

foreign import ccall "pango_script_get_sample_language" pango_script_get_sample_language :: 
    CUInt ->                                -- script : TInterface "Pango" "Script"
    IO (Ptr Language)


scriptGetSampleLanguage ::
    (MonadIO m) =>
    Script ->                               -- script
    m Language
scriptGetSampleLanguage script = liftIO $ do
    let script' = (fromIntegral . fromEnum) script
    result <- pango_script_get_sample_language script'
    checkUnexpectedReturnNULL "pango_script_get_sample_language" result
    result' <- (wrapBoxed Language) result
    return result'


-- function pango_script_for_unichar
-- 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 "Pango" "Script"
-- throws : False
-- Skip return : False

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


scriptForUnichar ::
    (MonadIO m) =>
    Char ->                                 -- ch
    m Script
scriptForUnichar ch = liftIO $ do
    let ch' = (fromIntegral . ord) ch
    result <- pango_script_for_unichar ch'
    let result' = (toEnum . fromIntegral) result
    return result'


-- function pango_scan_word
-- Args : [Arg {argName = "pos", argType = TBasicType TUTF8, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "out", argType = TInterface "GLib" "String", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pos", argType = TBasicType TUTF8, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "pango_scan_word" pango_scan_word :: 
    Ptr CString ->                          -- pos : TBasicType TUTF8
    Ptr GLib.String ->                      -- out : TInterface "GLib" "String"
    IO CInt

{-# DEPRECATED scanWord ["(Since version 1.38)"]#-}
scanWord ::
    (MonadIO m) =>
    T.Text ->                               -- pos
    m (Bool,T.Text,GLib.String)
scanWord pos = liftIO $ do
    pos' <- textToCString pos
    pos'' <- allocMem :: IO (Ptr CString)
    poke pos'' pos'
    out <- callocBoxedBytes 24 :: IO (Ptr GLib.String)
    result <- pango_scan_word pos'' out
    let result' = (/= 0) result
    pos''' <- peek pos''
    pos'''' <- cstringToText pos'''
    freeMem pos'''
    out' <- (wrapBoxed GLib.String) out
    freeMem pos''
    return (result', pos'''', out')


-- function pango_scan_string
-- Args : [Arg {argName = "pos", argType = TBasicType TUTF8, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "out", argType = TInterface "GLib" "String", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pos", argType = TBasicType TUTF8, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "pango_scan_string" pango_scan_string :: 
    Ptr CString ->                          -- pos : TBasicType TUTF8
    Ptr GLib.String ->                      -- out : TInterface "GLib" "String"
    IO CInt

{-# DEPRECATED scanString ["(Since version 1.38)"]#-}
scanString ::
    (MonadIO m) =>
    T.Text ->                               -- pos
    m (Bool,T.Text,GLib.String)
scanString pos = liftIO $ do
    pos' <- textToCString pos
    pos'' <- allocMem :: IO (Ptr CString)
    poke pos'' pos'
    out <- callocBoxedBytes 24 :: IO (Ptr GLib.String)
    result <- pango_scan_string pos'' out
    let result' = (/= 0) result
    pos''' <- peek pos''
    pos'''' <- cstringToText pos'''
    freeMem pos'''
    out' <- (wrapBoxed GLib.String) out
    freeMem pos''
    return (result', pos'''', out')


-- function pango_scan_int
-- Args : [Arg {argName = "pos", argType = TBasicType TUTF8, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "out", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "pos", argType = TBasicType TUTF8, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- returnType : TBasicType TBoolean
-- throws : False
-- Skip return : False

foreign import ccall "pango_scan_int" pango_scan_int :: 
    Ptr CString ->                          -- pos : TBasicType TUTF8
    Ptr Int32 ->                            -- out : TBasicType TInt32
    IO CInt

{-# DEPRECATED scanInt ["(Since version 1.38)"]#-}
scanInt ::
    (MonadIO m) =>
    T.Text ->                               -- pos
    m (Bool,T.Text,Int32)
scanInt pos = liftIO $ do
    pos' <- textToCString pos
    pos'' <- allocMem :: IO (Ptr CString)
    poke pos'' pos'
    out <- allocMem :: IO (Ptr Int32)
    result <- pango_scan_int pos'' out
    let result' = (/= 0) result
    pos''' <- peek pos''
    pos'''' <- cstringToText pos'''
    freeMem pos'''
    out' <- peek out
    freeMem pos''
    freeMem out
    return (result', pos'''', out')


-- function pango_reorder_items
-- Args : [Arg {argName = "logical_items", argType = TGList (TInterface "Pango" "Item"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "logical_items", argType = TGList (TInterface "Pango" "Item"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TGList (TInterface "Pango" "Item")
-- throws : False
-- Skip return : False

foreign import ccall "pango_reorder_items" pango_reorder_items :: 
    Ptr (GList (Ptr Item)) ->               -- logical_items : TGList (TInterface "Pango" "Item")
    IO (Ptr (GList (Ptr Item)))


reorderItems ::
    (MonadIO m) =>
    [Item] ->                               -- logical_items
    m [Item]
reorderItems logical_items = liftIO $ do
    let logical_items' = map unsafeManagedPtrGetPtr logical_items
    logical_items'' <- packGList logical_items'
    result <- pango_reorder_items logical_items''
    checkUnexpectedReturnNULL "pango_reorder_items" result
    result' <- unpackGList result
    result'' <- mapM (wrapBoxed Item) result'
    g_list_free result
    mapM_ touchManagedPtr logical_items
    g_list_free logical_items''
    return result''


-- function pango_read_line
-- Args : [Arg {argName = "stream", argType = TBasicType TVoid, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str", argType = TInterface "GLib" "String", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "stream", 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 "pango_read_line" pango_read_line :: 
    Ptr () ->                               -- stream : TBasicType TVoid
    Ptr GLib.String ->                      -- str : TInterface "GLib" "String"
    IO Int32

{-# DEPRECATED readLine ["(Since version 1.38)"]#-}
readLine ::
    (MonadIO m) =>
    Ptr () ->                               -- stream
    m (Int32,GLib.String)
readLine stream = liftIO $ do
    str <- callocBoxedBytes 24 :: IO (Ptr GLib.String)
    result <- pango_read_line stream str
    str' <- (wrapBoxed GLib.String) str
    return (result, str')


-- function pango_quantize_line_geometry
-- Args : [Arg {argName = "thickness", argType = TBasicType TInt32, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "position", argType = TBasicType TInt32, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "thickness", argType = TBasicType TInt32, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "position", argType = TBasicType TInt32, direction = DirectionInout, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_quantize_line_geometry" pango_quantize_line_geometry :: 
    Ptr Int32 ->                            -- thickness : TBasicType TInt32
    Ptr Int32 ->                            -- position : TBasicType TInt32
    IO ()


quantizeLineGeometry ::
    (MonadIO m) =>
    Int32 ->                                -- thickness
    Int32 ->                                -- position
    m (Int32,Int32)
quantizeLineGeometry thickness position = liftIO $ do
    thickness' <- allocMem :: IO (Ptr Int32)
    poke thickness' thickness
    position' <- allocMem :: IO (Ptr Int32)
    poke position' position
    pango_quantize_line_geometry thickness' position'
    thickness'' <- peek thickness'
    position'' <- peek position'
    freeMem thickness'
    freeMem position'
    return (thickness'', position'')


-- function pango_parse_weight
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "weight", argType = TInterface "Pango" "Weight", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "warn", argType = TBasicType TBoolean, 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 = "warn", 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 "pango_parse_weight" pango_parse_weight :: 
    CString ->                              -- str : TBasicType TUTF8
    Ptr CUInt ->                            -- weight : TInterface "Pango" "Weight"
    CInt ->                                 -- warn : TBasicType TBoolean
    IO CInt


parseWeight ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Bool ->                                 -- warn
    m (Bool,Weight)
parseWeight str warn = liftIO $ do
    str' <- textToCString str
    weight <- allocMem :: IO (Ptr CUInt)
    let warn' = (fromIntegral . fromEnum) warn
    result <- pango_parse_weight str' weight warn'
    let result' = (/= 0) result
    weight' <- peek weight
    let weight'' = (toEnum . fromIntegral) weight'
    freeMem str'
    freeMem weight
    return (result', weight'')


-- function pango_parse_variant
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "variant", argType = TInterface "Pango" "Variant", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "warn", argType = TBasicType TBoolean, 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 = "warn", 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 "pango_parse_variant" pango_parse_variant :: 
    CString ->                              -- str : TBasicType TUTF8
    Ptr CUInt ->                            -- variant : TInterface "Pango" "Variant"
    CInt ->                                 -- warn : TBasicType TBoolean
    IO CInt


parseVariant ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Bool ->                                 -- warn
    m (Bool,Variant)
parseVariant str warn = liftIO $ do
    str' <- textToCString str
    variant <- allocMem :: IO (Ptr CUInt)
    let warn' = (fromIntegral . fromEnum) warn
    result <- pango_parse_variant str' variant warn'
    let result' = (/= 0) result
    variant' <- peek variant
    let variant'' = (toEnum . fromIntegral) variant'
    freeMem str'
    freeMem variant
    return (result', variant'')


-- function pango_parse_style
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "style", argType = TInterface "Pango" "Style", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "warn", argType = TBasicType TBoolean, 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 = "warn", 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 "pango_parse_style" pango_parse_style :: 
    CString ->                              -- str : TBasicType TUTF8
    Ptr CUInt ->                            -- style : TInterface "Pango" "Style"
    CInt ->                                 -- warn : TBasicType TBoolean
    IO CInt


parseStyle ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Bool ->                                 -- warn
    m (Bool,Style)
parseStyle str warn = liftIO $ do
    str' <- textToCString str
    style <- allocMem :: IO (Ptr CUInt)
    let warn' = (fromIntegral . fromEnum) warn
    result <- pango_parse_style str' style warn'
    let result' = (/= 0) result
    style' <- peek style
    let style'' = (toEnum . fromIntegral) style'
    freeMem str'
    freeMem style
    return (result', style'')


-- function pango_parse_stretch
-- Args : [Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "stretch", argType = TInterface "Pango" "Stretch", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "warn", argType = TBasicType TBoolean, 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 = "warn", 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 "pango_parse_stretch" pango_parse_stretch :: 
    CString ->                              -- str : TBasicType TUTF8
    Ptr CUInt ->                            -- stretch : TInterface "Pango" "Stretch"
    CInt ->                                 -- warn : TBasicType TBoolean
    IO CInt


parseStretch ::
    (MonadIO m) =>
    T.Text ->                               -- str
    Bool ->                                 -- warn
    m (Bool,Stretch)
parseStretch str warn = liftIO $ do
    str' <- textToCString str
    stretch <- allocMem :: IO (Ptr CUInt)
    let warn' = (fromIntegral . fromEnum) warn
    result <- pango_parse_stretch str' stretch warn'
    let result' = (/= 0) result
    stretch' <- peek stretch
    let stretch'' = (toEnum . fromIntegral) stretch'
    freeMem str'
    freeMem stretch
    return (result', stretch'')


-- function pango_parse_markup
-- Args : [Arg {argName = "markup_text", 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},Arg {argName = "accel_marker", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attr_list", argType = TInterface "Pango" "AttrList", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "accel_char", argType = TBasicType TUniChar, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "markup_text", 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},Arg {argName = "accel_marker", argType = TBasicType TUniChar, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "pango_parse_markup" pango_parse_markup :: 
    CString ->                              -- markup_text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    CInt ->                                 -- accel_marker : TBasicType TUniChar
    Ptr (Ptr AttrList) ->                   -- attr_list : TInterface "Pango" "AttrList"
    Ptr CString ->                          -- text : TBasicType TUTF8
    Ptr CInt ->                             -- accel_char : TBasicType TUniChar
    Ptr (Ptr GError) ->                     -- error
    IO CInt


parseMarkup ::
    (MonadIO m) =>
    T.Text ->                               -- markup_text
    Int32 ->                                -- length
    Char ->                                 -- accel_marker
    m (AttrList,T.Text,Char)
parseMarkup markup_text length_ accel_marker = liftIO $ do
    markup_text' <- textToCString markup_text
    let accel_marker' = (fromIntegral . ord) accel_marker
    attr_list <- allocMem :: IO (Ptr (Ptr AttrList))
    text <- allocMem :: IO (Ptr CString)
    accel_char <- allocMem :: IO (Ptr CInt)
    onException (do
        _ <- propagateGError $ pango_parse_markup markup_text' length_ accel_marker' attr_list text accel_char
        attr_list' <- peek attr_list
        attr_list'' <- (wrapBoxed AttrList) attr_list'
        text' <- peek text
        text'' <- cstringToText text'
        freeMem text'
        accel_char' <- peek accel_char
        let accel_char'' = (chr . fromIntegral) accel_char'
        freeMem markup_text'
        freeMem attr_list
        freeMem text
        freeMem accel_char
        return (attr_list'', text'', accel_char'')
     ) (do
        freeMem markup_text'
        freeMem attr_list
        freeMem text
        freeMem accel_char
     )


-- function pango_parse_enum
-- Args : [Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "value", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "warn", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "possible_values", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "type", argType = TBasicType TGType, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "str", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "warn", 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 "pango_parse_enum" pango_parse_enum :: 
    CGType ->                               -- type : TBasicType TGType
    CString ->                              -- str : TBasicType TUTF8
    Ptr Int32 ->                            -- value : TBasicType TInt32
    CInt ->                                 -- warn : TBasicType TBoolean
    Ptr CString ->                          -- possible_values : TBasicType TUTF8
    IO CInt

{-# DEPRECATED parseEnum ["(Since version 1.38)"]#-}
parseEnum ::
    (MonadIO m) =>
    GType ->                                -- type
    Maybe (T.Text) ->                       -- str
    Bool ->                                 -- warn
    m (Bool,Int32,T.Text)
parseEnum type_ str warn = liftIO $ do
    let type_' = gtypeToCGType type_
    maybeStr <- case str of
        Nothing -> return nullPtr
        Just jStr -> do
            jStr' <- textToCString jStr
            return jStr'
    value <- allocMem :: IO (Ptr Int32)
    let warn' = (fromIntegral . fromEnum) warn
    possible_values <- allocMem :: IO (Ptr CString)
    result <- pango_parse_enum type_' maybeStr value warn' possible_values
    let result' = (/= 0) result
    value' <- peek value
    possible_values' <- peek possible_values
    possible_values'' <- cstringToText possible_values'
    freeMem possible_values'
    freeMem maybeStr
    freeMem value
    freeMem possible_values
    return (result', value', possible_values'')


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

foreign import ccall "pango_module_register" pango_module_register :: 
    Ptr IncludedModule ->                   -- module : TInterface "Pango" "IncludedModule"
    IO ()

{-# DEPRECATED moduleRegister ["(Since version 1.38)"]#-}
moduleRegister ::
    (MonadIO m) =>
    IncludedModule ->                       -- module
    m ()
moduleRegister module_ = liftIO $ do
    let module_' = unsafeManagedPtrGetPtr module_
    pango_module_register module_'
    touchManagedPtr module_
    return ()


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

foreign import ccall "pango_markup_parser_new" pango_markup_parser_new :: 
    CInt ->                                 -- accel_marker : TBasicType TUniChar
    IO (Ptr GLib.MarkupParseContext)


markupParserNew ::
    (MonadIO m) =>
    Char ->                                 -- accel_marker
    m GLib.MarkupParseContext
markupParserNew accel_marker = liftIO $ do
    let accel_marker' = (fromIntegral . ord) accel_marker
    result <- pango_markup_parser_new accel_marker'
    checkUnexpectedReturnNULL "pango_markup_parser_new" result
    result' <- (newBoxed GLib.MarkupParseContext) result
    return result'


-- function pango_markup_parser_finish
-- Args : [Arg {argName = "context", argType = TInterface "GLib" "MarkupParseContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attr_list", argType = TInterface "Pango" "AttrList", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "text", argType = TBasicType TUTF8, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "accel_char", argType = TBasicType TUniChar, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "context", argType = TInterface "GLib" "MarkupParseContext", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TBoolean
-- throws : True
-- Skip return : False

foreign import ccall "pango_markup_parser_finish" pango_markup_parser_finish :: 
    Ptr GLib.MarkupParseContext ->          -- context : TInterface "GLib" "MarkupParseContext"
    Ptr (Ptr AttrList) ->                   -- attr_list : TInterface "Pango" "AttrList"
    Ptr CString ->                          -- text : TBasicType TUTF8
    Ptr CInt ->                             -- accel_char : TBasicType TUniChar
    Ptr (Ptr GError) ->                     -- error
    IO CInt


markupParserFinish ::
    (MonadIO m) =>
    GLib.MarkupParseContext ->              -- context
    m (AttrList,T.Text,Char)
markupParserFinish context = liftIO $ do
    let context' = unsafeManagedPtrGetPtr context
    attr_list <- allocMem :: IO (Ptr (Ptr AttrList))
    text <- allocMem :: IO (Ptr CString)
    accel_char <- allocMem :: IO (Ptr CInt)
    onException (do
        _ <- propagateGError $ pango_markup_parser_finish context' attr_list text accel_char
        attr_list' <- peek attr_list
        attr_list'' <- (wrapBoxed AttrList) attr_list'
        text' <- peek text
        text'' <- cstringToText text'
        freeMem text'
        accel_char' <- peek accel_char
        let accel_char'' = (chr . fromIntegral) accel_char'
        touchManagedPtr context
        freeMem attr_list
        freeMem text
        freeMem accel_char
        return (attr_list'', text'', accel_char'')
     ) (do
        freeMem attr_list
        freeMem text
        freeMem accel_char
     )


-- function pango_lookup_aliases
-- Args : [Arg {argName = "fontname", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "families", argType = TCArray False (-1) 2 (TBasicType TUTF8), direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "n_families", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : [Arg {argName = "n_families", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- hInArgs : [Arg {argName = "fontname", 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 "pango_lookup_aliases" pango_lookup_aliases :: 
    CString ->                              -- fontname : TBasicType TUTF8
    Ptr (Ptr CString) ->                    -- families : TCArray False (-1) 2 (TBasicType TUTF8)
    Ptr Int32 ->                            -- n_families : TBasicType TInt32
    IO ()

{-# DEPRECATED lookupAliases ["(Since version 1.32)","This function is not thread-safe."]#-}
lookupAliases ::
    (MonadIO m) =>
    T.Text ->                               -- fontname
    m ([T.Text])
lookupAliases fontname = liftIO $ do
    fontname' <- textToCString fontname
    families <- allocMem :: IO (Ptr (Ptr CString))
    n_families <- allocMem :: IO (Ptr Int32)
    pango_lookup_aliases fontname' families n_families
    n_families' <- peek n_families
    families' <- peek families
    families'' <- (unpackUTF8CArrayWithLength n_families') families'
    (mapCArrayWithLength n_families') freeMem families'
    freeMem families'
    freeMem fontname'
    freeMem families
    freeMem n_families
    return families''


-- function pango_log2vis_get_embedding_levels
-- Args : [Arg {argName = "text", 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},Arg {argName = "pbase_dir", argType = TInterface "Pango" "Direction", 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 TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "pbase_dir", argType = TInterface "Pango" "Direction", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TUInt8
-- throws : False
-- Skip return : False

foreign import ccall "pango_log2vis_get_embedding_levels" pango_log2vis_get_embedding_levels :: 
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    CUInt ->                                -- pbase_dir : TInterface "Pango" "Direction"
    IO Word8


log2visGetEmbeddingLevels ::
    (MonadIO m) =>
    T.Text ->                               -- text
    Int32 ->                                -- length
    Direction ->                            -- pbase_dir
    m Word8
log2visGetEmbeddingLevels text length_ pbase_dir = liftIO $ do
    text' <- textToCString text
    let pbase_dir' = (fromIntegral . fromEnum) pbase_dir
    result <- pango_log2vis_get_embedding_levels text' length_ pbase_dir'
    freeMem text'
    return result


-- function pango_language_get_default
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Pango" "Language"
-- throws : False
-- Skip return : False

foreign import ccall "pango_language_get_default" pango_language_get_default :: 
    IO (Ptr Language)


languageGetDefault ::
    (MonadIO m) =>
    m Language
languageGetDefault  = liftIO $ do
    result <- pango_language_get_default
    checkUnexpectedReturnNULL "pango_language_get_default" result
    result' <- (newBoxed Language) result
    return result'


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

foreign import ccall "pango_language_from_string" pango_language_from_string :: 
    CString ->                              -- language : TBasicType TUTF8
    IO (Ptr Language)


languageFromString ::
    (MonadIO m) =>
    Maybe (T.Text) ->                       -- language
    m Language
languageFromString language = liftIO $ do
    maybeLanguage <- case language of
        Nothing -> return nullPtr
        Just jLanguage -> do
            jLanguage' <- textToCString jLanguage
            return jLanguage'
    result <- pango_language_from_string maybeLanguage
    checkUnexpectedReturnNULL "pango_language_from_string" result
    result' <- (newBoxed Language) result
    freeMem maybeLanguage
    return result'


-- function pango_itemize_with_base_dir
-- Args : [Arg {argName = "context", argType = TInterface "Pango" "Context", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base_dir", argType = TInterface "Pango" "Direction", direction = DirectionIn, mayBeNull = False, 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 = "start_index", argType = TBasicType TInt32, 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},Arg {argName = "attrs", argType = TInterface "Pango" "AttrList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cached_iter", argType = TInterface "Pango" "AttrIterator", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "context", argType = TInterface "Pango" "Context", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base_dir", argType = TInterface "Pango" "Direction", direction = DirectionIn, mayBeNull = False, 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 = "start_index", argType = TBasicType TInt32, 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},Arg {argName = "attrs", argType = TInterface "Pango" "AttrList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cached_iter", argType = TInterface "Pango" "AttrIterator", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TGList (TInterface "Pango" "Item")
-- throws : False
-- Skip return : False

foreign import ccall "pango_itemize_with_base_dir" pango_itemize_with_base_dir :: 
    Ptr Context ->                          -- context : TInterface "Pango" "Context"
    CUInt ->                                -- base_dir : TInterface "Pango" "Direction"
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- start_index : TBasicType TInt32
    Int32 ->                                -- length : TBasicType TInt32
    Ptr AttrList ->                         -- attrs : TInterface "Pango" "AttrList"
    Ptr AttrIterator ->                     -- cached_iter : TInterface "Pango" "AttrIterator"
    IO (Ptr (GList (Ptr Item)))


itemizeWithBaseDir ::
    (MonadIO m, ContextK a) =>
    a ->                                    -- context
    Direction ->                            -- base_dir
    T.Text ->                               -- text
    Int32 ->                                -- start_index
    Int32 ->                                -- length
    AttrList ->                             -- attrs
    Maybe (AttrIterator) ->                 -- cached_iter
    m [Item]
itemizeWithBaseDir context base_dir text start_index length_ attrs cached_iter = liftIO $ do
    let context' = unsafeManagedPtrCastPtr context
    let base_dir' = (fromIntegral . fromEnum) base_dir
    text' <- textToCString text
    let attrs' = unsafeManagedPtrGetPtr attrs
    maybeCached_iter <- case cached_iter of
        Nothing -> return nullPtr
        Just jCached_iter -> do
            let jCached_iter' = unsafeManagedPtrGetPtr jCached_iter
            return jCached_iter'
    result <- pango_itemize_with_base_dir context' base_dir' text' start_index length_ attrs' maybeCached_iter
    checkUnexpectedReturnNULL "pango_itemize_with_base_dir" result
    result' <- unpackGList result
    result'' <- mapM (wrapBoxed Item) result'
    g_list_free result
    touchManagedPtr context
    touchManagedPtr attrs
    whenJust cached_iter touchManagedPtr
    freeMem text'
    return result''


-- function pango_itemize
-- Args : [Arg {argName = "context", argType = TInterface "Pango" "Context", direction = DirectionIn, mayBeNull = False, 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 = "start_index", argType = TBasicType TInt32, 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},Arg {argName = "attrs", argType = TInterface "Pango" "AttrList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cached_iter", argType = TInterface "Pango" "AttrIterator", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "context", argType = TInterface "Pango" "Context", direction = DirectionIn, mayBeNull = False, 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 = "start_index", argType = TBasicType TInt32, 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},Arg {argName = "attrs", argType = TInterface "Pango" "AttrList", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "cached_iter", argType = TInterface "Pango" "AttrIterator", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TGList (TInterface "Pango" "Item")
-- throws : False
-- Skip return : False

foreign import ccall "pango_itemize" pango_itemize :: 
    Ptr Context ->                          -- context : TInterface "Pango" "Context"
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- start_index : TBasicType TInt32
    Int32 ->                                -- length : TBasicType TInt32
    Ptr AttrList ->                         -- attrs : TInterface "Pango" "AttrList"
    Ptr AttrIterator ->                     -- cached_iter : TInterface "Pango" "AttrIterator"
    IO (Ptr (GList (Ptr Item)))


itemize ::
    (MonadIO m, ContextK a) =>
    a ->                                    -- context
    T.Text ->                               -- text
    Int32 ->                                -- start_index
    Int32 ->                                -- length
    AttrList ->                             -- attrs
    Maybe (AttrIterator) ->                 -- cached_iter
    m [Item]
itemize context text start_index length_ attrs cached_iter = liftIO $ do
    let context' = unsafeManagedPtrCastPtr context
    text' <- textToCString text
    let attrs' = unsafeManagedPtrGetPtr attrs
    maybeCached_iter <- case cached_iter of
        Nothing -> return nullPtr
        Just jCached_iter -> do
            let jCached_iter' = unsafeManagedPtrGetPtr jCached_iter
            return jCached_iter'
    result <- pango_itemize context' text' start_index length_ attrs' maybeCached_iter
    checkUnexpectedReturnNULL "pango_itemize" result
    result' <- unpackGList result
    result'' <- mapM (wrapBoxed Item) result'
    g_list_free result
    touchManagedPtr context
    touchManagedPtr attrs
    whenJust cached_iter touchManagedPtr
    freeMem text'
    return result''


-- function pango_is_zero_width
-- 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 "pango_is_zero_width" pango_is_zero_width :: 
    CInt ->                                 -- ch : TBasicType TUniChar
    IO CInt


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


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

foreign import ccall "pango_gravity_to_rotation" pango_gravity_to_rotation :: 
    CUInt ->                                -- gravity : TInterface "Pango" "Gravity"
    IO CDouble


gravityToRotation ::
    (MonadIO m) =>
    Gravity ->                              -- gravity
    m Double
gravityToRotation gravity = liftIO $ do
    let gravity' = (fromIntegral . fromEnum) gravity
    result <- pango_gravity_to_rotation gravity'
    let result' = realToFrac result
    return result'


-- function pango_gravity_get_for_script_and_width
-- Args : [Arg {argName = "script", argType = TInterface "Pango" "Script", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "wide", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base_gravity", argType = TInterface "Pango" "Gravity", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hint", argType = TInterface "Pango" "GravityHint", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "script", argType = TInterface "Pango" "Script", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "wide", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base_gravity", argType = TInterface "Pango" "Gravity", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hint", argType = TInterface "Pango" "GravityHint", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Pango" "Gravity"
-- throws : False
-- Skip return : False

foreign import ccall "pango_gravity_get_for_script_and_width" pango_gravity_get_for_script_and_width :: 
    CUInt ->                                -- script : TInterface "Pango" "Script"
    CInt ->                                 -- wide : TBasicType TBoolean
    CUInt ->                                -- base_gravity : TInterface "Pango" "Gravity"
    CUInt ->                                -- hint : TInterface "Pango" "GravityHint"
    IO CUInt


gravityGetForScriptAndWidth ::
    (MonadIO m) =>
    Script ->                               -- script
    Bool ->                                 -- wide
    Gravity ->                              -- base_gravity
    GravityHint ->                          -- hint
    m Gravity
gravityGetForScriptAndWidth script wide base_gravity hint = liftIO $ do
    let script' = (fromIntegral . fromEnum) script
    let wide' = (fromIntegral . fromEnum) wide
    let base_gravity' = (fromIntegral . fromEnum) base_gravity
    let hint' = (fromIntegral . fromEnum) hint
    result <- pango_gravity_get_for_script_and_width script' wide' base_gravity' hint'
    let result' = (toEnum . fromIntegral) result
    return result'


-- function pango_gravity_get_for_script
-- Args : [Arg {argName = "script", argType = TInterface "Pango" "Script", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base_gravity", argType = TInterface "Pango" "Gravity", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hint", argType = TInterface "Pango" "GravityHint", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "script", argType = TInterface "Pango" "Script", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "base_gravity", argType = TInterface "Pango" "Gravity", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "hint", argType = TInterface "Pango" "GravityHint", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Pango" "Gravity"
-- throws : False
-- Skip return : False

foreign import ccall "pango_gravity_get_for_script" pango_gravity_get_for_script :: 
    CUInt ->                                -- script : TInterface "Pango" "Script"
    CUInt ->                                -- base_gravity : TInterface "Pango" "Gravity"
    CUInt ->                                -- hint : TInterface "Pango" "GravityHint"
    IO CUInt


gravityGetForScript ::
    (MonadIO m) =>
    Script ->                               -- script
    Gravity ->                              -- base_gravity
    GravityHint ->                          -- hint
    m Gravity
gravityGetForScript script base_gravity hint = liftIO $ do
    let script' = (fromIntegral . fromEnum) script
    let base_gravity' = (fromIntegral . fromEnum) base_gravity
    let hint' = (fromIntegral . fromEnum) hint
    result <- pango_gravity_get_for_script script' base_gravity' hint'
    let result' = (toEnum . fromIntegral) result
    return result'


-- function pango_gravity_get_for_matrix
-- Args : [Arg {argName = "matrix", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "matrix", argType = TInterface "Pango" "Matrix", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Pango" "Gravity"
-- throws : False
-- Skip return : False

foreign import ccall "pango_gravity_get_for_matrix" pango_gravity_get_for_matrix :: 
    Ptr Matrix ->                           -- matrix : TInterface "Pango" "Matrix"
    IO CUInt


gravityGetForMatrix ::
    (MonadIO m) =>
    Maybe (Matrix) ->                       -- matrix
    m Gravity
gravityGetForMatrix matrix = liftIO $ do
    maybeMatrix <- case matrix of
        Nothing -> return nullPtr
        Just jMatrix -> do
            let jMatrix' = unsafeManagedPtrGetPtr jMatrix
            return jMatrix'
    result <- pango_gravity_get_for_matrix maybeMatrix
    let result' = (toEnum . fromIntegral) result
    whenJust matrix touchManagedPtr
    return result'


-- function pango_get_sysconf_subdirectory
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "pango_get_sysconf_subdirectory" pango_get_sysconf_subdirectory :: 
    IO CString

{-# DEPRECATED getSysconfSubdirectory ["(Since version 1.38)"]#-}
getSysconfSubdirectory ::
    (MonadIO m) =>
    m T.Text
getSysconfSubdirectory  = liftIO $ do
    result <- pango_get_sysconf_subdirectory
    checkUnexpectedReturnNULL "pango_get_sysconf_subdirectory" result
    result' <- cstringToText result
    return result'


-- function pango_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 "pango_get_mirror_char" pango_get_mirror_char :: 
    CInt ->                                 -- ch : TBasicType TUniChar
    CInt ->                                 -- mirrored_ch : TBasicType TUniChar
    IO CInt


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


-- function pango_get_log_attrs
-- Args : [Arg {argName = "text", 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},Arg {argName = "level", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "language", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_attrs", argType = TCArray False (-1) 5 (TInterface "Pango" "LogAttr"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attrs_len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "attrs_len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "text", 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},Arg {argName = "level", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "language", argType = TInterface "Pango" "Language", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "log_attrs", argType = TCArray False (-1) 5 (TInterface "Pango" "LogAttr"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_get_log_attrs" pango_get_log_attrs :: 
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    Int32 ->                                -- level : TBasicType TInt32
    Ptr Language ->                         -- language : TInterface "Pango" "Language"
    Ptr LogAttr ->                          -- log_attrs : TCArray False (-1) 5 (TInterface "Pango" "LogAttr")
    Int32 ->                                -- attrs_len : TBasicType TInt32
    IO ()


getLogAttrs ::
    (MonadIO m) =>
    T.Text ->                               -- text
    Int32 ->                                -- length
    Int32 ->                                -- level
    Language ->                             -- language
    [LogAttr] ->                            -- log_attrs
    m ()
getLogAttrs text length_ level language log_attrs = liftIO $ do
    let attrs_len = fromIntegral $ length log_attrs
    text' <- textToCString text
    let language' = unsafeManagedPtrGetPtr language
    let log_attrs' = map unsafeManagedPtrGetPtr log_attrs
    log_attrs'' <- packBlockArray 52 log_attrs'
    pango_get_log_attrs text' length_ level language' log_attrs'' attrs_len
    touchManagedPtr language
    mapM_ touchManagedPtr log_attrs
    freeMem text'
    freeMem log_attrs''
    return ()


-- function pango_get_lib_subdirectory
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TBasicType TUTF8
-- throws : False
-- Skip return : False

foreign import ccall "pango_get_lib_subdirectory" pango_get_lib_subdirectory :: 
    IO CString

{-# DEPRECATED getLibSubdirectory ["(Since version 1.38)"]#-}
getLibSubdirectory ::
    (MonadIO m) =>
    m T.Text
getLibSubdirectory  = liftIO $ do
    result <- pango_get_lib_subdirectory
    checkUnexpectedReturnNULL "pango_get_lib_subdirectory" result
    result' <- cstringToText result
    return result'


-- function pango_font_description_from_string
-- 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 : TInterface "Pango" "FontDescription"
-- throws : False
-- Skip return : False

foreign import ccall "pango_font_description_from_string" pango_font_description_from_string :: 
    CString ->                              -- str : TBasicType TUTF8
    IO (Ptr FontDescription)


fontDescriptionFromString ::
    (MonadIO m) =>
    T.Text ->                               -- str
    m FontDescription
fontDescriptionFromString str = liftIO $ do
    str' <- textToCString str
    result <- pango_font_description_from_string str'
    checkUnexpectedReturnNULL "pango_font_description_from_string" result
    result' <- (wrapBoxed FontDescription) result
    freeMem str'
    return result'


-- function pango_find_paragraph_boundary
-- Args : [Arg {argName = "text", 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},Arg {argName = "paragraph_delimiter_index", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "next_paragraph_start", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- 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 TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_find_paragraph_boundary" pango_find_paragraph_boundary :: 
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    Ptr Int32 ->                            -- paragraph_delimiter_index : TBasicType TInt32
    Ptr Int32 ->                            -- next_paragraph_start : TBasicType TInt32
    IO ()


findParagraphBoundary ::
    (MonadIO m) =>
    T.Text ->                               -- text
    Int32 ->                                -- length
    m (Int32,Int32)
findParagraphBoundary text length_ = liftIO $ do
    text' <- textToCString text
    paragraph_delimiter_index <- allocMem :: IO (Ptr Int32)
    next_paragraph_start <- allocMem :: IO (Ptr Int32)
    pango_find_paragraph_boundary text' length_ paragraph_delimiter_index next_paragraph_start
    paragraph_delimiter_index' <- peek paragraph_delimiter_index
    next_paragraph_start' <- peek next_paragraph_start
    freeMem text'
    freeMem paragraph_delimiter_index
    freeMem next_paragraph_start
    return (paragraph_delimiter_index', next_paragraph_start')


-- function pango_find_base_dir
-- Args : [Arg {argName = "text", 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 = "text", 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 : TInterface "Pango" "Direction"
-- throws : False
-- Skip return : False

foreign import ccall "pango_find_base_dir" pango_find_base_dir :: 
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    IO CUInt


findBaseDir ::
    (MonadIO m) =>
    T.Text ->                               -- text
    Int32 ->                                -- length
    m Direction
findBaseDir text length_ = liftIO $ do
    text' <- textToCString text
    result <- pango_find_base_dir text' length_
    let result' = (toEnum . fromIntegral) result
    freeMem text'
    return result'


-- function pango_extents_to_pixels
-- Args : [Arg {argName = "inclusive", argType = TInterface "Pango" "Rectangle", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nearest", argType = TInterface "Pango" "Rectangle", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "inclusive", argType = TInterface "Pango" "Rectangle", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "nearest", argType = TInterface "Pango" "Rectangle", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_extents_to_pixels" pango_extents_to_pixels :: 
    Ptr Rectangle ->                        -- inclusive : TInterface "Pango" "Rectangle"
    Ptr Rectangle ->                        -- nearest : TInterface "Pango" "Rectangle"
    IO ()


extentsToPixels ::
    (MonadIO m) =>
    Maybe (Rectangle) ->                    -- inclusive
    Maybe (Rectangle) ->                    -- nearest
    m ()
extentsToPixels inclusive nearest = liftIO $ do
    maybeInclusive <- case inclusive of
        Nothing -> return nullPtr
        Just jInclusive -> do
            let jInclusive' = unsafeManagedPtrGetPtr jInclusive
            return jInclusive'
    maybeNearest <- case nearest of
        Nothing -> return nullPtr
        Just jNearest -> do
            let jNearest' = unsafeManagedPtrGetPtr jNearest
            return jNearest'
    pango_extents_to_pixels maybeInclusive maybeNearest
    whenJust inclusive touchManagedPtr
    whenJust nearest touchManagedPtr
    return ()


-- function pango_default_break
-- Args : [Arg {argName = "text", 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},Arg {argName = "analysis", argType = TInterface "Pango" "Analysis", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attrs", argType = TInterface "Pango" "LogAttr", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attrs_len", argType = TBasicType TInt32, 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 TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "analysis", argType = TInterface "Pango" "Analysis", direction = DirectionIn, mayBeNull = True, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attrs", argType = TInterface "Pango" "LogAttr", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attrs_len", 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 "pango_default_break" pango_default_break :: 
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    Ptr Analysis ->                         -- analysis : TInterface "Pango" "Analysis"
    Ptr LogAttr ->                          -- attrs : TInterface "Pango" "LogAttr"
    Int32 ->                                -- attrs_len : TBasicType TInt32
    IO ()


defaultBreak ::
    (MonadIO m) =>
    T.Text ->                               -- text
    Int32 ->                                -- length
    Maybe (Analysis) ->                     -- analysis
    LogAttr ->                              -- attrs
    Int32 ->                                -- attrs_len
    m ()
defaultBreak text length_ analysis attrs attrs_len = liftIO $ do
    text' <- textToCString text
    maybeAnalysis <- case analysis of
        Nothing -> return nullPtr
        Just jAnalysis -> do
            let jAnalysis' = unsafeManagedPtrGetPtr jAnalysis
            return jAnalysis'
    let attrs' = unsafeManagedPtrGetPtr attrs
    pango_default_break text' length_ maybeAnalysis attrs' attrs_len
    whenJust analysis touchManagedPtr
    touchManagedPtr attrs
    freeMem text'
    return ()


-- function pango_config_key_get_system
-- Args : [Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "key", 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 "pango_config_key_get_system" pango_config_key_get_system :: 
    CString ->                              -- key : TBasicType TUTF8
    IO CString

{-# DEPRECATED configKeyGetSystem ["(Since version 1.38)"]#-}
configKeyGetSystem ::
    (MonadIO m) =>
    T.Text ->                               -- key
    m T.Text
configKeyGetSystem key = liftIO $ do
    key' <- textToCString key
    result <- pango_config_key_get_system key'
    checkUnexpectedReturnNULL "pango_config_key_get_system" result
    result' <- cstringToText result
    freeMem result
    freeMem key'
    return result'


-- function pango_config_key_get
-- Args : [Arg {argName = "key", argType = TBasicType TUTF8, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "key", 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 "pango_config_key_get" pango_config_key_get :: 
    CString ->                              -- key : TBasicType TUTF8
    IO CString

{-# DEPRECATED configKeyGet ["(Since version 1.38)"]#-}
configKeyGet ::
    (MonadIO m) =>
    T.Text ->                               -- key
    m T.Text
configKeyGet key = liftIO $ do
    key' <- textToCString key
    result <- pango_config_key_get key'
    checkUnexpectedReturnNULL "pango_config_key_get" result
    result' <- cstringToText result
    freeMem result
    freeMem key'
    return result'


-- function pango_break
-- Args : [Arg {argName = "text", 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},Arg {argName = "analysis", argType = TInterface "Pango" "Analysis", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attrs", argType = TCArray False (-1) 4 (TInterface "Pango" "LogAttr"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attrs_len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : [Arg {argName = "attrs_len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- hInArgs : [Arg {argName = "text", 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},Arg {argName = "analysis", argType = TInterface "Pango" "Analysis", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "attrs", argType = TCArray False (-1) 4 (TInterface "Pango" "LogAttr"), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_break" pango_break :: 
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    Ptr Analysis ->                         -- analysis : TInterface "Pango" "Analysis"
    Ptr LogAttr ->                          -- attrs : TCArray False (-1) 4 (TInterface "Pango" "LogAttr")
    Int32 ->                                -- attrs_len : TBasicType TInt32
    IO ()


break ::
    (MonadIO m) =>
    T.Text ->                               -- text
    Int32 ->                                -- length
    Analysis ->                             -- analysis
    [LogAttr] ->                            -- attrs
    m ()
break text length_ analysis attrs = liftIO $ do
    let attrs_len = fromIntegral $ length attrs
    text' <- textToCString text
    let analysis' = unsafeManagedPtrGetPtr analysis
    let attrs' = map unsafeManagedPtrGetPtr attrs
    attrs'' <- packBlockArray 52 attrs'
    pango_break text' length_ analysis' attrs'' attrs_len
    touchManagedPtr analysis
    mapM_ touchManagedPtr attrs
    freeMem text'
    freeMem attrs''
    return ()


-- function pango_bidi_type_for_unichar
-- 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 "Pango" "BidiType"
-- throws : False
-- Skip return : False

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


bidiTypeForUnichar ::
    (MonadIO m) =>
    Char ->                                 -- ch
    m BidiType
bidiTypeForUnichar ch = liftIO $ do
    let ch' = (fromIntegral . ord) ch
    result <- pango_bidi_type_for_unichar ch'
    let result' = (toEnum . fromIntegral) result
    return result'


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

foreign import ccall "pango_attr_type_register" pango_attr_type_register :: 
    CString ->                              -- name : TBasicType TUTF8
    IO CUInt


attrTypeRegister ::
    (MonadIO m) =>
    T.Text ->                               -- name
    m AttrType
attrTypeRegister name = liftIO $ do
    name' <- textToCString name
    result <- pango_attr_type_register name'
    let result' = (toEnum . fromIntegral) result
    freeMem name'
    return result'


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

foreign import ccall "pango_attr_type_get_name" pango_attr_type_get_name :: 
    CUInt ->                                -- type : TInterface "Pango" "AttrType"
    IO CString


attrTypeGetName ::
    (MonadIO m) =>
    AttrType ->                             -- type
    m T.Text
attrTypeGetName type_ = liftIO $ do
    let type_' = (fromIntegral . fromEnum) type_
    result <- pango_attr_type_get_name type_'
    checkUnexpectedReturnNULL "pango_attr_type_get_name" result
    result' <- cstringToText result
    return result'