{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' is an iterator over the clusters in a
-- t'GI.Pango.Structs.GlyphItem.GlyphItem'.  The \<firstterm>forward direction\<\/firstterm> of the
-- iterator is the logical direction of text.  That is, with increasing
-- /@startIndex@/ and /@startChar@/ values.  If /@glyphItem@/ is right-to-left
-- (that is, if \<literal>/@glyphItem@/->item->analysis.level\<\/literal> is odd),
-- then /@startGlyph@/ decreases as the iterator moves forward.  Moreover,
-- in right-to-left cases, /@startGlyph@/ is greater than /@endGlyph@/.
-- 
-- An iterator should be initialized using either of
-- 'GI.Pango.Structs.GlyphItemIter.glyphItemIterInitStart' and
-- 'GI.Pango.Structs.GlyphItemIter.glyphItemIterInitEnd', for forward and backward iteration
-- respectively, and walked over using any desired mixture of
-- 'GI.Pango.Structs.GlyphItemIter.glyphItemIterNextCluster' and
-- 'GI.Pango.Structs.GlyphItemIter.glyphItemIterPrevCluster'.  A common idiom for doing a
-- forward iteration over the clusters is:
-- \<programlisting>
-- PangoGlyphItemIter cluster_iter;
-- gboolean have_cluster;
-- 
-- for (have_cluster = pango_glyph_item_iter_init_start (&amp;cluster_iter,
--                                                       glyph_item, text);
--      have_cluster;
--      have_cluster = pango_glyph_item_iter_next_cluster (&amp;cluster_iter))
-- {
--   ...
-- }
-- \<\/programlisting>
-- 
-- Note that /@text@/ is the start of the text for layout, which is then
-- indexed by \<literal>/@glyphItem@/->item->offset\<\/literal> to get to the
-- text of /@glyphItem@/.  The /@startIndex@/ and /@endIndex@/ values can directly
-- index into /@text@/.  The /@startGlyph@/, /@endGlyph@/, /@startChar@/, and /@endChar@/
-- values however are zero-based for the /@glyphItem@/.  For each cluster, the
-- item pointed at by the start variables is included in the cluster while
-- the one pointed at by end variables is not.
-- 
-- None of the members of a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' should be modified manually.
-- 
-- /Since: 1.22/

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

module GI.Pango.Structs.GlyphItemIter
    ( 

-- * Exported types
    GlyphItemIter(..)                       ,
    newZeroGlyphItemIter                    ,
    noGlyphItemIter                         ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolveGlyphItemIterMethod              ,
#endif


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    GlyphItemIterCopyMethodInfo             ,
#endif
    glyphItemIterCopy                       ,


-- ** free #method:free#

#if defined(ENABLE_OVERLOADING)
    GlyphItemIterFreeMethodInfo             ,
#endif
    glyphItemIterFree                       ,


-- ** initEnd #method:initEnd#

#if defined(ENABLE_OVERLOADING)
    GlyphItemIterInitEndMethodInfo          ,
#endif
    glyphItemIterInitEnd                    ,


-- ** initStart #method:initStart#

#if defined(ENABLE_OVERLOADING)
    GlyphItemIterInitStartMethodInfo        ,
#endif
    glyphItemIterInitStart                  ,


-- ** nextCluster #method:nextCluster#

#if defined(ENABLE_OVERLOADING)
    GlyphItemIterNextClusterMethodInfo      ,
#endif
    glyphItemIterNextCluster                ,


-- ** prevCluster #method:prevCluster#

#if defined(ENABLE_OVERLOADING)
    GlyphItemIterPrevClusterMethodInfo      ,
#endif
    glyphItemIterPrevCluster                ,




 -- * Properties
-- ** endChar #attr:endChar#
-- | /No description available in the introspection data./

    getGlyphItemIterEndChar                 ,
#if defined(ENABLE_OVERLOADING)
    glyphItemIter_endChar                   ,
#endif
    setGlyphItemIterEndChar                 ,


-- ** endGlyph #attr:endGlyph#
-- | /No description available in the introspection data./

    getGlyphItemIterEndGlyph                ,
#if defined(ENABLE_OVERLOADING)
    glyphItemIter_endGlyph                  ,
#endif
    setGlyphItemIterEndGlyph                ,


-- ** endIndex #attr:endIndex#
-- | /No description available in the introspection data./

    getGlyphItemIterEndIndex                ,
#if defined(ENABLE_OVERLOADING)
    glyphItemIter_endIndex                  ,
#endif
    setGlyphItemIterEndIndex                ,


-- ** glyphItem #attr:glyphItem#
-- | /No description available in the introspection data./

    clearGlyphItemIterGlyphItem             ,
    getGlyphItemIterGlyphItem               ,
#if defined(ENABLE_OVERLOADING)
    glyphItemIter_glyphItem                 ,
#endif
    setGlyphItemIterGlyphItem               ,


-- ** startChar #attr:startChar#
-- | /No description available in the introspection data./

    getGlyphItemIterStartChar               ,
#if defined(ENABLE_OVERLOADING)
    glyphItemIter_startChar                 ,
#endif
    setGlyphItemIterStartChar               ,


-- ** startGlyph #attr:startGlyph#
-- | /No description available in the introspection data./

    getGlyphItemIterStartGlyph              ,
#if defined(ENABLE_OVERLOADING)
    glyphItemIter_startGlyph                ,
#endif
    setGlyphItemIterStartGlyph              ,


-- ** startIndex #attr:startIndex#
-- | /No description available in the introspection data./

    getGlyphItemIterStartIndex              ,
#if defined(ENABLE_OVERLOADING)
    glyphItemIter_startIndex                ,
#endif
    setGlyphItemIterStartIndex              ,


-- ** text #attr:text#
-- | /No description available in the introspection data./

    clearGlyphItemIterText                  ,
    getGlyphItemIterText                    ,
#if defined(ENABLE_OVERLOADING)
    glyphItemIter_text                      ,
#endif
    setGlyphItemIterText                    ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL

import {-# SOURCE #-} qualified GI.Pango.Structs.GlyphItem as Pango.GlyphItem

-- | Memory-managed wrapper type.
newtype GlyphItemIter = GlyphItemIter (ManagedPtr GlyphItemIter)
    deriving (GlyphItemIter -> GlyphItemIter -> Bool
(GlyphItemIter -> GlyphItemIter -> Bool)
-> (GlyphItemIter -> GlyphItemIter -> Bool) -> Eq GlyphItemIter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GlyphItemIter -> GlyphItemIter -> Bool
$c/= :: GlyphItemIter -> GlyphItemIter -> Bool
== :: GlyphItemIter -> GlyphItemIter -> Bool
$c== :: GlyphItemIter -> GlyphItemIter -> Bool
Eq)
foreign import ccall "pango_glyph_item_iter_get_type" c_pango_glyph_item_iter_get_type :: 
    IO GType

instance BoxedObject GlyphItemIter where
    boxedType :: GlyphItemIter -> IO GType
boxedType _ = IO GType
c_pango_glyph_item_iter_get_type

-- | Convert 'GlyphItemIter' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue GlyphItemIter where
    toGValue :: GlyphItemIter -> IO GValue
toGValue o :: GlyphItemIter
o = do
        GType
gtype <- IO GType
c_pango_glyph_item_iter_get_type
        GlyphItemIter -> (Ptr GlyphItemIter -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GlyphItemIter
o (GType
-> (GValue -> Ptr GlyphItemIter -> IO ())
-> Ptr GlyphItemIter
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr GlyphItemIter -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
        
    fromGValue :: GValue -> IO GlyphItemIter
fromGValue gv :: GValue
gv = do
        Ptr GlyphItemIter
ptr <- GValue -> IO (Ptr GlyphItemIter)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr GlyphItemIter)
        (ManagedPtr GlyphItemIter -> GlyphItemIter)
-> Ptr GlyphItemIter -> IO GlyphItemIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr GlyphItemIter -> GlyphItemIter
GlyphItemIter Ptr GlyphItemIter
ptr
        
    

-- | Construct a `GlyphItemIter` struct initialized to zero.
newZeroGlyphItemIter :: MonadIO m => m GlyphItemIter
newZeroGlyphItemIter :: m GlyphItemIter
newZeroGlyphItemIter = IO GlyphItemIter -> m GlyphItemIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GlyphItemIter -> m GlyphItemIter)
-> IO GlyphItemIter -> m GlyphItemIter
forall a b. (a -> b) -> a -> b
$ Int -> IO (Ptr GlyphItemIter)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 40 IO (Ptr GlyphItemIter)
-> (Ptr GlyphItemIter -> IO GlyphItemIter) -> IO GlyphItemIter
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr GlyphItemIter -> GlyphItemIter)
-> Ptr GlyphItemIter -> IO GlyphItemIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GlyphItemIter -> GlyphItemIter
GlyphItemIter

instance tag ~ 'AttrSet => Constructible GlyphItemIter tag where
    new :: (ManagedPtr GlyphItemIter -> GlyphItemIter)
-> [AttrOp GlyphItemIter tag] -> m GlyphItemIter
new _ attrs :: [AttrOp GlyphItemIter tag]
attrs = do
        GlyphItemIter
o <- m GlyphItemIter
forall (m :: * -> *). MonadIO m => m GlyphItemIter
newZeroGlyphItemIter
        GlyphItemIter -> [AttrOp GlyphItemIter 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set GlyphItemIter
o [AttrOp GlyphItemIter tag]
[AttrOp GlyphItemIter 'AttrSet]
attrs
        GlyphItemIter -> m GlyphItemIter
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphItemIter
o


-- | A convenience alias for `Nothing` :: `Maybe` `GlyphItemIter`.
noGlyphItemIter :: Maybe GlyphItemIter
noGlyphItemIter :: Maybe GlyphItemIter
noGlyphItemIter = Maybe GlyphItemIter
forall a. Maybe a
Nothing

-- | Get the value of the “@glyph_item@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' glyphItemIter #glyphItem
-- @
getGlyphItemIterGlyphItem :: MonadIO m => GlyphItemIter -> m (Maybe Pango.GlyphItem.GlyphItem)
getGlyphItemIterGlyphItem :: GlyphItemIter -> m (Maybe GlyphItem)
getGlyphItemIterGlyphItem s :: GlyphItemIter
s = IO (Maybe GlyphItem) -> m (Maybe GlyphItem)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GlyphItem) -> m (Maybe GlyphItem))
-> IO (Maybe GlyphItem) -> m (Maybe GlyphItem)
forall a b. (a -> b) -> a -> b
$ GlyphItemIter
-> (Ptr GlyphItemIter -> IO (Maybe GlyphItem))
-> IO (Maybe GlyphItem)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO (Maybe GlyphItem))
 -> IO (Maybe GlyphItem))
-> (Ptr GlyphItemIter -> IO (Maybe GlyphItem))
-> IO (Maybe GlyphItem)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr GlyphItem
val <- Ptr (Ptr GlyphItem) -> IO (Ptr GlyphItem)
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr (Ptr GlyphItem)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO (Ptr Pango.GlyphItem.GlyphItem)
    Maybe GlyphItem
result <- Ptr GlyphItem
-> (Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr GlyphItem
val ((Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem))
-> (Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr GlyphItem
val' -> do
        GlyphItem
val'' <- ((ManagedPtr GlyphItem -> GlyphItem)
-> Ptr GlyphItem -> IO GlyphItem
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr GlyphItem -> GlyphItem
Pango.GlyphItem.GlyphItem) Ptr GlyphItem
val'
        GlyphItem -> IO GlyphItem
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphItem
val''
    Maybe GlyphItem -> IO (Maybe GlyphItem)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GlyphItem
result

-- | Set the value of the “@glyph_item@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' glyphItemIter [ #glyphItem 'Data.GI.Base.Attributes.:=' value ]
-- @
setGlyphItemIterGlyphItem :: MonadIO m => GlyphItemIter -> Ptr Pango.GlyphItem.GlyphItem -> m ()
setGlyphItemIterGlyphItem :: GlyphItemIter -> Ptr GlyphItem -> m ()
setGlyphItemIterGlyphItem s :: GlyphItemIter
s val :: Ptr GlyphItem
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr (Ptr GlyphItem) -> Ptr GlyphItem -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr (Ptr GlyphItem)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr GlyphItem
val :: Ptr Pango.GlyphItem.GlyphItem)

-- | Set the value of the “@glyph_item@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #glyphItem
-- @
clearGlyphItemIterGlyphItem :: MonadIO m => GlyphItemIter -> m ()
clearGlyphItemIterGlyphItem :: GlyphItemIter -> m ()
clearGlyphItemIterGlyphItem s :: GlyphItemIter
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr (Ptr GlyphItem) -> Ptr GlyphItem -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr (Ptr GlyphItem)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr GlyphItem
forall a. Ptr a
FP.nullPtr :: Ptr Pango.GlyphItem.GlyphItem)

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterGlyphItemFieldInfo
instance AttrInfo GlyphItemIterGlyphItemFieldInfo where
    type AttrBaseTypeConstraint GlyphItemIterGlyphItemFieldInfo = (~) GlyphItemIter
    type AttrAllowedOps GlyphItemIterGlyphItemFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint GlyphItemIterGlyphItemFieldInfo = (~) (Ptr Pango.GlyphItem.GlyphItem)
    type AttrTransferTypeConstraint GlyphItemIterGlyphItemFieldInfo = (~)(Ptr Pango.GlyphItem.GlyphItem)
    type AttrTransferType GlyphItemIterGlyphItemFieldInfo = (Ptr Pango.GlyphItem.GlyphItem)
    type AttrGetType GlyphItemIterGlyphItemFieldInfo = Maybe Pango.GlyphItem.GlyphItem
    type AttrLabel GlyphItemIterGlyphItemFieldInfo = "glyph_item"
    type AttrOrigin GlyphItemIterGlyphItemFieldInfo = GlyphItemIter
    attrGet = getGlyphItemIterGlyphItem
    attrSet = setGlyphItemIterGlyphItem
    attrConstruct = undefined
    attrClear = clearGlyphItemIterGlyphItem
    attrTransfer _ v = do
        return v

glyphItemIter_glyphItem :: AttrLabelProxy "glyphItem"
glyphItemIter_glyphItem = AttrLabelProxy

#endif


-- | Get the value of the “@text@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' glyphItemIter #text
-- @
getGlyphItemIterText :: MonadIO m => GlyphItemIter -> m (Maybe T.Text)
getGlyphItemIterText :: GlyphItemIter -> m (Maybe Text)
getGlyphItemIterText s :: GlyphItemIter
s = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ GlyphItemIter
-> (Ptr GlyphItemIter -> IO (Maybe Text)) -> IO (Maybe Text)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO (Maybe Text)) -> IO (Maybe Text))
-> (Ptr GlyphItemIter -> IO (Maybe Text)) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    CString
val <- Ptr CString -> IO CString
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO CString
    Maybe Text
result <- CString -> (CString -> IO Text) -> IO (Maybe Text)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull CString
val ((CString -> IO Text) -> IO (Maybe Text))
-> (CString -> IO Text) -> IO (Maybe Text)
forall a b. (a -> b) -> a -> b
$ \val' :: CString
val' -> do
        Text
val'' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
val'
        Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
val''
    Maybe Text -> IO (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Text
result

-- | Set the value of the “@text@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' glyphItemIter [ #text 'Data.GI.Base.Attributes.:=' value ]
-- @
setGlyphItemIterText :: MonadIO m => GlyphItemIter -> CString -> m ()
setGlyphItemIterText :: GlyphItemIter -> CString -> m ()
setGlyphItemIterText s :: GlyphItemIter
s val :: CString
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (CString
val :: CString)

-- | Set the value of the “@text@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #text
-- @
clearGlyphItemIterText :: MonadIO m => GlyphItemIter -> m ()
clearGlyphItemIterText :: GlyphItemIter -> m ()
clearGlyphItemIterText s :: GlyphItemIter
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr CString -> CString -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr CString
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (CString
forall a. Ptr a
FP.nullPtr :: CString)

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterTextFieldInfo
instance AttrInfo GlyphItemIterTextFieldInfo where
    type AttrBaseTypeConstraint GlyphItemIterTextFieldInfo = (~) GlyphItemIter
    type AttrAllowedOps GlyphItemIterTextFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
    type AttrSetTypeConstraint GlyphItemIterTextFieldInfo = (~) CString
    type AttrTransferTypeConstraint GlyphItemIterTextFieldInfo = (~)CString
    type AttrTransferType GlyphItemIterTextFieldInfo = CString
    type AttrGetType GlyphItemIterTextFieldInfo = Maybe T.Text
    type AttrLabel GlyphItemIterTextFieldInfo = "text"
    type AttrOrigin GlyphItemIterTextFieldInfo = GlyphItemIter
    attrGet = getGlyphItemIterText
    attrSet = setGlyphItemIterText
    attrConstruct = undefined
    attrClear = clearGlyphItemIterText
    attrTransfer _ v = do
        return v

glyphItemIter_text :: AttrLabelProxy "text"
glyphItemIter_text = AttrLabelProxy

#endif


-- | Get the value of the “@start_glyph@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' glyphItemIter #startGlyph
-- @
getGlyphItemIterStartGlyph :: MonadIO m => GlyphItemIter -> m Int32
getGlyphItemIterStartGlyph :: GlyphItemIter -> m Int32
getGlyphItemIterStartGlyph s :: GlyphItemIter
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO Int32) -> IO Int32)
-> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@start_glyph@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' glyphItemIter [ #startGlyph 'Data.GI.Base.Attributes.:=' value ]
-- @
setGlyphItemIterStartGlyph :: MonadIO m => GlyphItemIter -> Int32 -> m ()
setGlyphItemIterStartGlyph :: GlyphItemIter -> Int32 -> m ()
setGlyphItemIterStartGlyph s :: GlyphItemIter
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterStartGlyphFieldInfo
instance AttrInfo GlyphItemIterStartGlyphFieldInfo where
    type AttrBaseTypeConstraint GlyphItemIterStartGlyphFieldInfo = (~) GlyphItemIter
    type AttrAllowedOps GlyphItemIterStartGlyphFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphItemIterStartGlyphFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphItemIterStartGlyphFieldInfo = (~)Int32
    type AttrTransferType GlyphItemIterStartGlyphFieldInfo = Int32
    type AttrGetType GlyphItemIterStartGlyphFieldInfo = Int32
    type AttrLabel GlyphItemIterStartGlyphFieldInfo = "start_glyph"
    type AttrOrigin GlyphItemIterStartGlyphFieldInfo = GlyphItemIter
    attrGet = getGlyphItemIterStartGlyph
    attrSet = setGlyphItemIterStartGlyph
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

glyphItemIter_startGlyph :: AttrLabelProxy "startGlyph"
glyphItemIter_startGlyph = AttrLabelProxy

#endif


-- | Get the value of the “@start_index@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' glyphItemIter #startIndex
-- @
getGlyphItemIterStartIndex :: MonadIO m => GlyphItemIter -> m Int32
getGlyphItemIterStartIndex :: GlyphItemIter -> m Int32
getGlyphItemIterStartIndex s :: GlyphItemIter
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO Int32) -> IO Int32)
-> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@start_index@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' glyphItemIter [ #startIndex 'Data.GI.Base.Attributes.:=' value ]
-- @
setGlyphItemIterStartIndex :: MonadIO m => GlyphItemIter -> Int32 -> m ()
setGlyphItemIterStartIndex :: GlyphItemIter -> Int32 -> m ()
setGlyphItemIterStartIndex s :: GlyphItemIter
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 20) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterStartIndexFieldInfo
instance AttrInfo GlyphItemIterStartIndexFieldInfo where
    type AttrBaseTypeConstraint GlyphItemIterStartIndexFieldInfo = (~) GlyphItemIter
    type AttrAllowedOps GlyphItemIterStartIndexFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphItemIterStartIndexFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphItemIterStartIndexFieldInfo = (~)Int32
    type AttrTransferType GlyphItemIterStartIndexFieldInfo = Int32
    type AttrGetType GlyphItemIterStartIndexFieldInfo = Int32
    type AttrLabel GlyphItemIterStartIndexFieldInfo = "start_index"
    type AttrOrigin GlyphItemIterStartIndexFieldInfo = GlyphItemIter
    attrGet = getGlyphItemIterStartIndex
    attrSet = setGlyphItemIterStartIndex
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

glyphItemIter_startIndex :: AttrLabelProxy "startIndex"
glyphItemIter_startIndex = AttrLabelProxy

#endif


-- | Get the value of the “@start_char@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' glyphItemIter #startChar
-- @
getGlyphItemIterStartChar :: MonadIO m => GlyphItemIter -> m Int32
getGlyphItemIterStartChar :: GlyphItemIter -> m Int32
getGlyphItemIterStartChar s :: GlyphItemIter
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO Int32) -> IO Int32)
-> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@start_char@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' glyphItemIter [ #startChar 'Data.GI.Base.Attributes.:=' value ]
-- @
setGlyphItemIterStartChar :: MonadIO m => GlyphItemIter -> Int32 -> m ()
setGlyphItemIterStartChar :: GlyphItemIter -> Int32 -> m ()
setGlyphItemIterStartChar s :: GlyphItemIter
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterStartCharFieldInfo
instance AttrInfo GlyphItemIterStartCharFieldInfo where
    type AttrBaseTypeConstraint GlyphItemIterStartCharFieldInfo = (~) GlyphItemIter
    type AttrAllowedOps GlyphItemIterStartCharFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphItemIterStartCharFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphItemIterStartCharFieldInfo = (~)Int32
    type AttrTransferType GlyphItemIterStartCharFieldInfo = Int32
    type AttrGetType GlyphItemIterStartCharFieldInfo = Int32
    type AttrLabel GlyphItemIterStartCharFieldInfo = "start_char"
    type AttrOrigin GlyphItemIterStartCharFieldInfo = GlyphItemIter
    attrGet = getGlyphItemIterStartChar
    attrSet = setGlyphItemIterStartChar
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

glyphItemIter_startChar :: AttrLabelProxy "startChar"
glyphItemIter_startChar = AttrLabelProxy

#endif


-- | Get the value of the “@end_glyph@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' glyphItemIter #endGlyph
-- @
getGlyphItemIterEndGlyph :: MonadIO m => GlyphItemIter -> m Int32
getGlyphItemIterEndGlyph :: GlyphItemIter -> m Int32
getGlyphItemIterEndGlyph s :: GlyphItemIter
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO Int32) -> IO Int32)
-> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@end_glyph@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' glyphItemIter [ #endGlyph 'Data.GI.Base.Attributes.:=' value ]
-- @
setGlyphItemIterEndGlyph :: MonadIO m => GlyphItemIter -> Int32 -> m ()
setGlyphItemIterEndGlyph :: GlyphItemIter -> Int32 -> m ()
setGlyphItemIterEndGlyph s :: GlyphItemIter
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterEndGlyphFieldInfo
instance AttrInfo GlyphItemIterEndGlyphFieldInfo where
    type AttrBaseTypeConstraint GlyphItemIterEndGlyphFieldInfo = (~) GlyphItemIter
    type AttrAllowedOps GlyphItemIterEndGlyphFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphItemIterEndGlyphFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphItemIterEndGlyphFieldInfo = (~)Int32
    type AttrTransferType GlyphItemIterEndGlyphFieldInfo = Int32
    type AttrGetType GlyphItemIterEndGlyphFieldInfo = Int32
    type AttrLabel GlyphItemIterEndGlyphFieldInfo = "end_glyph"
    type AttrOrigin GlyphItemIterEndGlyphFieldInfo = GlyphItemIter
    attrGet = getGlyphItemIterEndGlyph
    attrSet = setGlyphItemIterEndGlyph
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

glyphItemIter_endGlyph :: AttrLabelProxy "endGlyph"
glyphItemIter_endGlyph = AttrLabelProxy

#endif


-- | Get the value of the “@end_index@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' glyphItemIter #endIndex
-- @
getGlyphItemIterEndIndex :: MonadIO m => GlyphItemIter -> m Int32
getGlyphItemIterEndIndex :: GlyphItemIter -> m Int32
getGlyphItemIterEndIndex s :: GlyphItemIter
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO Int32) -> IO Int32)
-> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@end_index@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' glyphItemIter [ #endIndex 'Data.GI.Base.Attributes.:=' value ]
-- @
setGlyphItemIterEndIndex :: MonadIO m => GlyphItemIter -> Int32 -> m ()
setGlyphItemIterEndIndex :: GlyphItemIter -> Int32 -> m ()
setGlyphItemIterEndIndex s :: GlyphItemIter
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 32) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterEndIndexFieldInfo
instance AttrInfo GlyphItemIterEndIndexFieldInfo where
    type AttrBaseTypeConstraint GlyphItemIterEndIndexFieldInfo = (~) GlyphItemIter
    type AttrAllowedOps GlyphItemIterEndIndexFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphItemIterEndIndexFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphItemIterEndIndexFieldInfo = (~)Int32
    type AttrTransferType GlyphItemIterEndIndexFieldInfo = Int32
    type AttrGetType GlyphItemIterEndIndexFieldInfo = Int32
    type AttrLabel GlyphItemIterEndIndexFieldInfo = "end_index"
    type AttrOrigin GlyphItemIterEndIndexFieldInfo = GlyphItemIter
    attrGet = getGlyphItemIterEndIndex
    attrSet = setGlyphItemIterEndIndex
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

glyphItemIter_endIndex :: AttrLabelProxy "endIndex"
glyphItemIter_endIndex = AttrLabelProxy

#endif


-- | Get the value of the “@end_char@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' glyphItemIter #endChar
-- @
getGlyphItemIterEndChar :: MonadIO m => GlyphItemIter -> m Int32
getGlyphItemIterEndChar :: GlyphItemIter -> m Int32
getGlyphItemIterEndChar s :: GlyphItemIter
s = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO Int32) -> IO Int32)
-> (Ptr GlyphItemIter -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@end_char@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' glyphItemIter [ #endChar 'Data.GI.Base.Attributes.:=' value ]
-- @
setGlyphItemIterEndChar :: MonadIO m => GlyphItemIter -> Int32 -> m ()
setGlyphItemIterEndChar :: GlyphItemIter -> Int32 -> m ()
setGlyphItemIterEndChar s :: GlyphItemIter
s val :: Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ GlyphItemIter -> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr GlyphItemIter
s ((Ptr GlyphItemIter -> IO ()) -> IO ())
-> (Ptr GlyphItemIter -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr GlyphItemIter
ptr -> do
    Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr GlyphItemIter
ptr Ptr GlyphItemIter -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 36) (Int32
val :: Int32)

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterEndCharFieldInfo
instance AttrInfo GlyphItemIterEndCharFieldInfo where
    type AttrBaseTypeConstraint GlyphItemIterEndCharFieldInfo = (~) GlyphItemIter
    type AttrAllowedOps GlyphItemIterEndCharFieldInfo = '[ 'AttrSet, 'AttrGet]
    type AttrSetTypeConstraint GlyphItemIterEndCharFieldInfo = (~) Int32
    type AttrTransferTypeConstraint GlyphItemIterEndCharFieldInfo = (~)Int32
    type AttrTransferType GlyphItemIterEndCharFieldInfo = Int32
    type AttrGetType GlyphItemIterEndCharFieldInfo = Int32
    type AttrLabel GlyphItemIterEndCharFieldInfo = "end_char"
    type AttrOrigin GlyphItemIterEndCharFieldInfo = GlyphItemIter
    attrGet = getGlyphItemIterEndChar
    attrSet = setGlyphItemIterEndChar
    attrConstruct = undefined
    attrClear = undefined
    attrTransfer _ v = do
        return v

glyphItemIter_endChar :: AttrLabelProxy "endChar"
glyphItemIter_endChar = AttrLabelProxy

#endif



#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GlyphItemIter
type instance O.AttributeList GlyphItemIter = GlyphItemIterAttributeList
type GlyphItemIterAttributeList = ('[ '("glyphItem", GlyphItemIterGlyphItemFieldInfo), '("text", GlyphItemIterTextFieldInfo), '("startGlyph", GlyphItemIterStartGlyphFieldInfo), '("startIndex", GlyphItemIterStartIndexFieldInfo), '("startChar", GlyphItemIterStartCharFieldInfo), '("endGlyph", GlyphItemIterEndGlyphFieldInfo), '("endIndex", GlyphItemIterEndIndexFieldInfo), '("endChar", GlyphItemIterEndCharFieldInfo)] :: [(Symbol, *)])
#endif

-- method GlyphItemIter::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "orig"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "GlyphItemIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoGlyphItemIter, may be %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Pango" , name = "GlyphItemIter" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_item_iter_copy" pango_glyph_item_iter_copy :: 
    Ptr GlyphItemIter ->                    -- orig : TInterface (Name {namespace = "Pango", name = "GlyphItemIter"})
    IO (Ptr GlyphItemIter)

-- | Make a shallow copy of an existing t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' structure.
-- 
-- /Since: 1.22/
glyphItemIterCopy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GlyphItemIter
    -- ^ /@orig@/: a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter', may be 'P.Nothing'
    -> m (Maybe GlyphItemIter)
    -- ^ __Returns:__ the newly allocated t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter', which should
    --               be freed with 'GI.Pango.Structs.GlyphItemIter.glyphItemIterFree', or 'P.Nothing'
    --               if /@orig@/ was 'P.Nothing'.
glyphItemIterCopy :: GlyphItemIter -> m (Maybe GlyphItemIter)
glyphItemIterCopy orig :: GlyphItemIter
orig = IO (Maybe GlyphItemIter) -> m (Maybe GlyphItemIter)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GlyphItemIter) -> m (Maybe GlyphItemIter))
-> IO (Maybe GlyphItemIter) -> m (Maybe GlyphItemIter)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GlyphItemIter
orig' <- GlyphItemIter -> IO (Ptr GlyphItemIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItemIter
orig
    Ptr GlyphItemIter
result <- Ptr GlyphItemIter -> IO (Ptr GlyphItemIter)
pango_glyph_item_iter_copy Ptr GlyphItemIter
orig'
    Maybe GlyphItemIter
maybeResult <- Ptr GlyphItemIter
-> (Ptr GlyphItemIter -> IO GlyphItemIter)
-> IO (Maybe GlyphItemIter)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GlyphItemIter
result ((Ptr GlyphItemIter -> IO GlyphItemIter)
 -> IO (Maybe GlyphItemIter))
-> (Ptr GlyphItemIter -> IO GlyphItemIter)
-> IO (Maybe GlyphItemIter)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GlyphItemIter
result' -> do
        GlyphItemIter
result'' <- ((ManagedPtr GlyphItemIter -> GlyphItemIter)
-> Ptr GlyphItemIter -> IO GlyphItemIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr GlyphItemIter -> GlyphItemIter
GlyphItemIter) Ptr GlyphItemIter
result'
        GlyphItemIter -> IO GlyphItemIter
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphItemIter
result''
    GlyphItemIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItemIter
orig
    Maybe GlyphItemIter -> IO (Maybe GlyphItemIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GlyphItemIter
maybeResult

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterCopyMethodInfo
instance (signature ~ (m (Maybe GlyphItemIter)), MonadIO m) => O.MethodInfo GlyphItemIterCopyMethodInfo GlyphItemIter signature where
    overloadedMethod = glyphItemIterCopy

#endif

-- method GlyphItemIter::free
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "GlyphItemIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoGlyphItemIter, may be %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_item_iter_free" pango_glyph_item_iter_free :: 
    Ptr GlyphItemIter ->                    -- iter : TInterface (Name {namespace = "Pango", name = "GlyphItemIter"})
    IO ()

-- | Frees a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' created by 'GI.Pango.Structs.GlyphItemIter.glyphItemIterCopy'.
-- 
-- /Since: 1.22/
glyphItemIterFree ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GlyphItemIter
    -- ^ /@iter@/: a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter', may be 'P.Nothing'
    -> m ()
glyphItemIterFree :: GlyphItemIter -> m ()
glyphItemIterFree iter :: GlyphItemIter
iter = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GlyphItemIter
iter' <- GlyphItemIter -> IO (Ptr GlyphItemIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItemIter
iter
    Ptr GlyphItemIter -> IO ()
pango_glyph_item_iter_free Ptr GlyphItemIter
iter'
    GlyphItemIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItemIter
iter
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo GlyphItemIterFreeMethodInfo GlyphItemIter signature where
    overloadedMethod = glyphItemIterFree

#endif

-- method GlyphItemIter::init_end
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "GlyphItemIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoGlyphItemIter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "glyph_item"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "GlyphItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the glyph item to iterate over"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "text corresponding to the glyph item"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_item_iter_init_end" pango_glyph_item_iter_init_end :: 
    Ptr GlyphItemIter ->                    -- iter : TInterface (Name {namespace = "Pango", name = "GlyphItemIter"})
    Ptr Pango.GlyphItem.GlyphItem ->        -- glyph_item : TInterface (Name {namespace = "Pango", name = "GlyphItem"})
    CString ->                              -- text : TBasicType TUTF8
    IO CInt

-- | Initializes a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' structure to point to the
-- last cluster in a glyph item.
-- See t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' for details of cluster orders.
-- 
-- /Since: 1.22/
glyphItemIterInitEnd ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GlyphItemIter
    -- ^ /@iter@/: a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter'
    -> Pango.GlyphItem.GlyphItem
    -- ^ /@glyphItem@/: the glyph item to iterate over
    -> T.Text
    -- ^ /@text@/: text corresponding to the glyph item
    -> m Bool
    -- ^ __Returns:__ 'P.False' if there are no clusters in the glyph item
glyphItemIterInitEnd :: GlyphItemIter -> GlyphItem -> Text -> m Bool
glyphItemIterInitEnd iter :: GlyphItemIter
iter glyphItem :: GlyphItem
glyphItem text :: Text
text = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GlyphItemIter
iter' <- GlyphItemIter -> IO (Ptr GlyphItemIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItemIter
iter
    Ptr GlyphItem
glyphItem' <- GlyphItem -> IO (Ptr GlyphItem)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItem
glyphItem
    CString
text' <- Text -> IO CString
textToCString Text
text
    CInt
result <- Ptr GlyphItemIter -> Ptr GlyphItem -> CString -> IO CInt
pango_glyph_item_iter_init_end Ptr GlyphItemIter
iter' Ptr GlyphItem
glyphItem' CString
text'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    GlyphItemIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItemIter
iter
    GlyphItem -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItem
glyphItem
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterInitEndMethodInfo
instance (signature ~ (Pango.GlyphItem.GlyphItem -> T.Text -> m Bool), MonadIO m) => O.MethodInfo GlyphItemIterInitEndMethodInfo GlyphItemIter signature where
    overloadedMethod = glyphItemIterInitEnd

#endif

-- method GlyphItemIter::init_start
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iter"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "GlyphItemIter" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoGlyphItemIter"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "glyph_item"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "GlyphItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the glyph item to iterate over"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "text corresponding to the glyph item"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_glyph_item_iter_init_start" pango_glyph_item_iter_init_start :: 
    Ptr GlyphItemIter ->                    -- iter : TInterface (Name {namespace = "Pango", name = "GlyphItemIter"})
    Ptr Pango.GlyphItem.GlyphItem ->        -- glyph_item : TInterface (Name {namespace = "Pango", name = "GlyphItem"})
    CString ->                              -- text : TBasicType TUTF8
    IO CInt

-- | Initializes a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' structure to point to the
-- first cluster in a glyph item.
-- See t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' for details of cluster orders.
-- 
-- /Since: 1.22/
glyphItemIterInitStart ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GlyphItemIter
    -- ^ /@iter@/: a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter'
    -> Pango.GlyphItem.GlyphItem
    -- ^ /@glyphItem@/: the glyph item to iterate over
    -> T.Text
    -- ^ /@text@/: text corresponding to the glyph item
    -> m Bool
    -- ^ __Returns:__ 'P.False' if there are no clusters in the glyph item
glyphItemIterInitStart :: GlyphItemIter -> GlyphItem -> Text -> m Bool
glyphItemIterInitStart iter :: GlyphItemIter
iter glyphItem :: GlyphItem
glyphItem text :: Text
text = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GlyphItemIter
iter' <- GlyphItemIter -> IO (Ptr GlyphItemIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItemIter
iter
    Ptr GlyphItem
glyphItem' <- GlyphItem -> IO (Ptr GlyphItem)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItem
glyphItem
    CString
text' <- Text -> IO CString
textToCString Text
text
    CInt
result <- Ptr GlyphItemIter -> Ptr GlyphItem -> CString -> IO CInt
pango_glyph_item_iter_init_start Ptr GlyphItemIter
iter' Ptr GlyphItem
glyphItem' CString
text'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    GlyphItemIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItemIter
iter
    GlyphItem -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItem
glyphItem
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterInitStartMethodInfo
instance (signature ~ (Pango.GlyphItem.GlyphItem -> T.Text -> m Bool), MonadIO m) => O.MethodInfo GlyphItemIterInitStartMethodInfo GlyphItemIter signature where
    overloadedMethod = glyphItemIterInitStart

#endif

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

foreign import ccall "pango_glyph_item_iter_next_cluster" pango_glyph_item_iter_next_cluster :: 
    Ptr GlyphItemIter ->                    -- iter : TInterface (Name {namespace = "Pango", name = "GlyphItemIter"})
    IO CInt

-- | Advances the iterator to the next cluster in the glyph item.
-- See t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' for details of cluster orders.
-- 
-- /Since: 1.22/
glyphItemIterNextCluster ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GlyphItemIter
    -- ^ /@iter@/: a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the iterator was advanced, 'P.False' if we were already on the
    --  last cluster.
glyphItemIterNextCluster :: GlyphItemIter -> m Bool
glyphItemIterNextCluster iter :: GlyphItemIter
iter = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GlyphItemIter
iter' <- GlyphItemIter -> IO (Ptr GlyphItemIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItemIter
iter
    CInt
result <- Ptr GlyphItemIter -> IO CInt
pango_glyph_item_iter_next_cluster Ptr GlyphItemIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    GlyphItemIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItemIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterNextClusterMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo GlyphItemIterNextClusterMethodInfo GlyphItemIter signature where
    overloadedMethod = glyphItemIterNextCluster

#endif

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

foreign import ccall "pango_glyph_item_iter_prev_cluster" pango_glyph_item_iter_prev_cluster :: 
    Ptr GlyphItemIter ->                    -- iter : TInterface (Name {namespace = "Pango", name = "GlyphItemIter"})
    IO CInt

-- | Moves the iterator to the preceding cluster in the glyph item.
-- See t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter' for details of cluster orders.
-- 
-- /Since: 1.22/
glyphItemIterPrevCluster ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GlyphItemIter
    -- ^ /@iter@/: a t'GI.Pango.Structs.GlyphItemIter.GlyphItemIter'
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the iterator was moved, 'P.False' if we were already on the
    --  first cluster.
glyphItemIterPrevCluster :: GlyphItemIter -> m Bool
glyphItemIterPrevCluster iter :: GlyphItemIter
iter = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr GlyphItemIter
iter' <- GlyphItemIter -> IO (Ptr GlyphItemIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItemIter
iter
    CInt
result <- Ptr GlyphItemIter -> IO CInt
pango_glyph_item_iter_prev_cluster Ptr GlyphItemIter
iter'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    GlyphItemIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItemIter
iter
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GlyphItemIterPrevClusterMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo GlyphItemIterPrevClusterMethodInfo GlyphItemIter signature where
    overloadedMethod = glyphItemIterPrevCluster

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveGlyphItemIterMethod (t :: Symbol) (o :: *) :: * where
    ResolveGlyphItemIterMethod "copy" o = GlyphItemIterCopyMethodInfo
    ResolveGlyphItemIterMethod "free" o = GlyphItemIterFreeMethodInfo
    ResolveGlyphItemIterMethod "initEnd" o = GlyphItemIterInitEndMethodInfo
    ResolveGlyphItemIterMethod "initStart" o = GlyphItemIterInitStartMethodInfo
    ResolveGlyphItemIterMethod "nextCluster" o = GlyphItemIterNextClusterMethodInfo
    ResolveGlyphItemIterMethod "prevCluster" o = GlyphItemIterPrevClusterMethodInfo
    ResolveGlyphItemIterMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveGlyphItemIterMethod t GlyphItemIter, O.MethodInfo info GlyphItemIter p) => OL.IsLabel t (GlyphItemIter -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#endif