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

The #PangoGlyphString structure is used to store strings
of glyphs with geometry and visual attribute information.
The storage for the glyph information is owned
by the structure which simplifies memory management.
-}

module GI.Pango.Structs.GlyphString
    ( 

-- * Exported types
    GlyphString(..)                         ,
    noGlyphString                           ,


 -- * Methods
-- ** glyphStringCopy
    glyphStringCopy                         ,


-- ** glyphStringExtents
    glyphStringExtents                      ,


-- ** glyphStringExtentsRange
    glyphStringExtentsRange                 ,


-- ** glyphStringFree
    glyphStringFree                         ,


-- ** glyphStringGetLogicalWidths
    glyphStringGetLogicalWidths             ,


-- ** glyphStringGetWidth
    glyphStringGetWidth                     ,


-- ** glyphStringIndexToX
    glyphStringIndexToX                     ,


-- ** glyphStringNew
    glyphStringNew                          ,


-- ** glyphStringSetSize
    glyphStringSetSize                      ,


-- ** glyphStringXToIndex
    glyphStringXToIndex                     ,




 -- * Properties
-- ** LogClusters
    glyphStringReadLogClusters              ,


-- ** NumGlyphs
    glyphStringReadNumGlyphs                ,




    ) 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

newtype GlyphString = GlyphString (ForeignPtr GlyphString)
foreign import ccall "pango_glyph_string_get_type" c_pango_glyph_string_get_type :: 
    IO GType

instance BoxedObject GlyphString where
    boxedType _ = c_pango_glyph_string_get_type

noGlyphString :: Maybe GlyphString
noGlyphString = Nothing

glyphStringReadNumGlyphs :: GlyphString -> IO Int32
glyphStringReadNumGlyphs s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 0) :: IO Int32
    return val

-- XXX Skipped getter for "GlyphString:glyphs" :: Not implemented: "Don't know how to unpack C array of type TCArray False (-1) 0 (TInterface \"Pango\" \"GlyphInfo\")"

glyphStringReadLogClusters :: GlyphString -> IO Int32
glyphStringReadLogClusters s = withManagedPtr s $ \ptr -> do
    val <- peek (ptr `plusPtr` 16) :: IO Int32
    return val

-- method GlyphString::new
-- method type : Constructor
-- Args : []
-- Lengths : []
-- hInArgs : []
-- returnType : TInterface "Pango" "GlyphString"
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_string_new" pango_glyph_string_new :: 
    IO (Ptr GlyphString)


glyphStringNew ::
    (MonadIO m) =>
    m GlyphString
glyphStringNew  = liftIO $ do
    result <- pango_glyph_string_new
    checkUnexpectedReturnNULL "pango_glyph_string_new" result
    result' <- (wrapBoxed GlyphString) result
    return result'

-- method GlyphString::copy
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TInterface "Pango" "GlyphString"
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_string_copy" pango_glyph_string_copy :: 
    Ptr GlyphString ->                      -- _obj : TInterface "Pango" "GlyphString"
    IO (Ptr GlyphString)


glyphStringCopy ::
    (MonadIO m) =>
    GlyphString ->                          -- _obj
    m GlyphString
glyphStringCopy _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- pango_glyph_string_copy _obj'
    checkUnexpectedReturnNULL "pango_glyph_string_copy" result
    result' <- (wrapBoxed GlyphString) result
    touchManagedPtr _obj
    return result'

-- method GlyphString::extents
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "font", argType = TInterface "Pango" "Font", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ink_rect", argType = TInterface "Pango" "Rectangle", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "logical_rect", argType = TInterface "Pango" "Rectangle", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "font", argType = TInterface "Pango" "Font", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_string_extents" pango_glyph_string_extents :: 
    Ptr GlyphString ->                      -- _obj : TInterface "Pango" "GlyphString"
    Ptr Font ->                             -- font : TInterface "Pango" "Font"
    Ptr Rectangle ->                        -- ink_rect : TInterface "Pango" "Rectangle"
    Ptr Rectangle ->                        -- logical_rect : TInterface "Pango" "Rectangle"
    IO ()


glyphStringExtents ::
    (MonadIO m, FontK a) =>
    GlyphString ->                          -- _obj
    a ->                                    -- font
    m (Rectangle,Rectangle)
glyphStringExtents _obj font = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let font' = unsafeManagedPtrCastPtr font
    ink_rect <- callocBytes 16 :: IO (Ptr Rectangle)
    logical_rect <- callocBytes 16 :: IO (Ptr Rectangle)
    pango_glyph_string_extents _obj' font' ink_rect logical_rect
    ink_rect' <- (wrapPtr Rectangle) ink_rect
    logical_rect' <- (wrapPtr Rectangle) logical_rect
    touchManagedPtr _obj
    touchManagedPtr font
    return (ink_rect', logical_rect')

-- method GlyphString::extents_range
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "font", argType = TInterface "Pango" "Font", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "ink_rect", argType = TInterface "Pango" "Rectangle", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "logical_rect", argType = TInterface "Pango" "Rectangle", direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "start", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "end", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "font", argType = TInterface "Pango" "Font", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_string_extents_range" pango_glyph_string_extents_range :: 
    Ptr GlyphString ->                      -- _obj : TInterface "Pango" "GlyphString"
    Int32 ->                                -- start : TBasicType TInt32
    Int32 ->                                -- end : TBasicType TInt32
    Ptr Font ->                             -- font : TInterface "Pango" "Font"
    Ptr Rectangle ->                        -- ink_rect : TInterface "Pango" "Rectangle"
    Ptr Rectangle ->                        -- logical_rect : TInterface "Pango" "Rectangle"
    IO ()


glyphStringExtentsRange ::
    (MonadIO m, FontK a) =>
    GlyphString ->                          -- _obj
    Int32 ->                                -- start
    Int32 ->                                -- end
    a ->                                    -- font
    m (Rectangle,Rectangle)
glyphStringExtentsRange _obj start end font = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    let font' = unsafeManagedPtrCastPtr font
    ink_rect <- callocBytes 16 :: IO (Ptr Rectangle)
    logical_rect <- callocBytes 16 :: IO (Ptr Rectangle)
    pango_glyph_string_extents_range _obj' start end font' ink_rect logical_rect
    ink_rect' <- (wrapPtr Rectangle) ink_rect
    logical_rect' <- (wrapPtr Rectangle) logical_rect
    touchManagedPtr _obj
    touchManagedPtr font
    return (ink_rect', logical_rect')

-- method GlyphString::free
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", 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_glyph_string_free" pango_glyph_string_free :: 
    Ptr GlyphString ->                      -- _obj : TInterface "Pango" "GlyphString"
    IO ()


glyphStringFree ::
    (MonadIO m) =>
    GlyphString ->                          -- _obj
    m ()
glyphStringFree _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    pango_glyph_string_free _obj'
    touchManagedPtr _obj
    return ()

-- method GlyphString::get_logical_widths
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", 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 = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "embedding_level", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "logical_widths", argType = TCArray False (-1) (-1) (TBasicType TInt32), direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", 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 = "length", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "embedding_level", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "logical_widths", argType = TCArray False (-1) (-1) (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_glyph_string_get_logical_widths" pango_glyph_string_get_logical_widths :: 
    Ptr GlyphString ->                      -- _obj : TInterface "Pango" "GlyphString"
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    Int32 ->                                -- embedding_level : TBasicType TInt32
    Ptr Int32 ->                            -- logical_widths : TCArray False (-1) (-1) (TBasicType TInt32)
    IO ()


glyphStringGetLogicalWidths ::
    (MonadIO m) =>
    GlyphString ->                          -- _obj
    T.Text ->                               -- text
    Int32 ->                                -- length
    Int32 ->                                -- embedding_level
    Ptr Int32 ->                            -- logical_widths
    m ()
glyphStringGetLogicalWidths _obj text length_ embedding_level logical_widths = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    text' <- textToCString text
    pango_glyph_string_get_logical_widths _obj' text' length_ embedding_level logical_widths
    touchManagedPtr _obj
    freeMem text'
    return ()

-- method GlyphString::get_width
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TInt32
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_string_get_width" pango_glyph_string_get_width :: 
    Ptr GlyphString ->                      -- _obj : TInterface "Pango" "GlyphString"
    IO Int32


glyphStringGetWidth ::
    (MonadIO m) =>
    GlyphString ->                          -- _obj
    m Int32
glyphStringGetWidth _obj = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    result <- pango_glyph_string_get_width _obj'
    touchManagedPtr _obj
    return result

-- method GlyphString::index_to_x
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", 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 = "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 = "index_", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "trailing", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "x_pos", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", 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 = "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 = "index_", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "trailing", argType = TBasicType TBoolean, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- returnType : TBasicType TVoid
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_string_index_to_x" pango_glyph_string_index_to_x :: 
    Ptr GlyphString ->                      -- _obj : TInterface "Pango" "GlyphString"
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    Ptr Analysis ->                         -- analysis : TInterface "Pango" "Analysis"
    Int32 ->                                -- index_ : TBasicType TInt32
    CInt ->                                 -- trailing : TBasicType TBoolean
    Ptr Int32 ->                            -- x_pos : TBasicType TInt32
    IO ()


glyphStringIndexToX ::
    (MonadIO m) =>
    GlyphString ->                          -- _obj
    T.Text ->                               -- text
    Int32 ->                                -- length
    Analysis ->                             -- analysis
    Int32 ->                                -- index_
    Bool ->                                 -- trailing
    m (Int32)
glyphStringIndexToX _obj text length_ analysis index_ trailing = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    text' <- textToCString text
    let analysis' = unsafeManagedPtrGetPtr analysis
    let trailing' = (fromIntegral . fromEnum) trailing
    x_pos <- allocMem :: IO (Ptr Int32)
    pango_glyph_string_index_to_x _obj' text' length_ analysis' index_ trailing' x_pos
    x_pos' <- peek x_pos
    touchManagedPtr _obj
    touchManagedPtr analysis
    freeMem text'
    freeMem x_pos
    return x_pos'

-- method GlyphString::set_size
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "new_len", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "new_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_glyph_string_set_size" pango_glyph_string_set_size :: 
    Ptr GlyphString ->                      -- _obj : TInterface "Pango" "GlyphString"
    Int32 ->                                -- new_len : TBasicType TInt32
    IO ()


glyphStringSetSize ::
    (MonadIO m) =>
    GlyphString ->                          -- _obj
    Int32 ->                                -- new_len
    m ()
glyphStringSetSize _obj new_len = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    pango_glyph_string_set_size _obj' new_len
    touchManagedPtr _obj
    return ()

-- method GlyphString::x_to_index
-- method type : OrdinaryMethod
-- Args : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", 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 = "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 = "x_pos", argType = TBasicType TInt32, direction = DirectionIn, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferNothing},Arg {argName = "index_", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything},Arg {argName = "trailing", argType = TBasicType TInt32, direction = DirectionOut, mayBeNull = False, argScope = ScopeTypeInvalid, argClosure = -1, argDestroy = -1, transfer = TransferEverything}]
-- Lengths : []
-- hInArgs : [Arg {argName = "_obj", argType = TInterface "Pango" "GlyphString", 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 = "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 = "x_pos", 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_glyph_string_x_to_index" pango_glyph_string_x_to_index :: 
    Ptr GlyphString ->                      -- _obj : TInterface "Pango" "GlyphString"
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt32
    Ptr Analysis ->                         -- analysis : TInterface "Pango" "Analysis"
    Int32 ->                                -- x_pos : TBasicType TInt32
    Ptr Int32 ->                            -- index_ : TBasicType TInt32
    Ptr Int32 ->                            -- trailing : TBasicType TInt32
    IO ()


glyphStringXToIndex ::
    (MonadIO m) =>
    GlyphString ->                          -- _obj
    T.Text ->                               -- text
    Int32 ->                                -- length
    Analysis ->                             -- analysis
    Int32 ->                                -- x_pos
    m (Int32,Int32)
glyphStringXToIndex _obj text length_ analysis x_pos = liftIO $ do
    let _obj' = unsafeManagedPtrGetPtr _obj
    text' <- textToCString text
    let analysis' = unsafeManagedPtrGetPtr analysis
    index_ <- allocMem :: IO (Ptr Int32)
    trailing <- allocMem :: IO (Ptr Int32)
    pango_glyph_string_x_to_index _obj' text' length_ analysis' x_pos index_ trailing
    index_' <- peek index_
    trailing' <- peek trailing
    touchManagedPtr _obj
    touchManagedPtr analysis
    freeMem text'
    freeMem index_
    freeMem trailing
    return (index_', trailing')