{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Pango.Structs.AttrIterator.AttrIterator' structure is used to represent an
-- iterator through a t'GI.Pango.Structs.AttrList.AttrList'. A new iterator is created
-- with @/pango_attr_list_get_iterator()/@. Once the iterator
-- is created, it can be advanced through the style changes
-- in the text using 'GI.Pango.Structs.AttrIterator.attrIteratorNext'. At each
-- style change, the range of the current style segment and the
-- attributes currently in effect can be queried.

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

module GI.Pango.Structs.AttrIterator
    ( 

-- * Exported types
    AttrIterator(..)                        ,
    noAttrIterator                          ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveAttrIteratorMethod               ,
#endif


-- ** destroy #method:destroy#

#if defined(ENABLE_OVERLOADING)
    AttrIteratorDestroyMethodInfo           ,
#endif
    attrIteratorDestroy                     ,


-- ** getAttrs #method:getAttrs#

#if defined(ENABLE_OVERLOADING)
    AttrIteratorGetAttrsMethodInfo          ,
#endif
    attrIteratorGetAttrs                    ,


-- ** getFont #method:getFont#

#if defined(ENABLE_OVERLOADING)
    AttrIteratorGetFontMethodInfo           ,
#endif
    attrIteratorGetFont                     ,


-- ** next #method:next#

#if defined(ENABLE_OVERLOADING)
    AttrIteratorNextMethodInfo              ,
#endif
    attrIteratorNext                        ,


-- ** range #method:range#

#if defined(ENABLE_OVERLOADING)
    AttrIteratorRangeMethodInfo             ,
#endif
    attrIteratorRange                       ,




    ) 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.Attribute as Pango.Attribute
import {-# SOURCE #-} qualified GI.Pango.Structs.FontDescription as Pango.FontDescription
import {-# SOURCE #-} qualified GI.Pango.Structs.Language as Pango.Language

-- | Memory-managed wrapper type.
newtype AttrIterator = AttrIterator (ManagedPtr AttrIterator)
    deriving (AttrIterator -> AttrIterator -> Bool
(AttrIterator -> AttrIterator -> Bool)
-> (AttrIterator -> AttrIterator -> Bool) -> Eq AttrIterator
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttrIterator -> AttrIterator -> Bool
$c/= :: AttrIterator -> AttrIterator -> Bool
== :: AttrIterator -> AttrIterator -> Bool
$c== :: AttrIterator -> AttrIterator -> Bool
Eq)
-- XXX Wrapping a foreign struct/union with no known destructor or size, leak?
instance WrappedPtr AttrIterator where
    wrappedPtrCalloc :: IO (Ptr AttrIterator)
wrappedPtrCalloc = Ptr AttrIterator -> IO (Ptr AttrIterator)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AttrIterator
forall a. Ptr a
nullPtr
    wrappedPtrCopy :: AttrIterator -> IO AttrIterator
wrappedPtrCopy = AttrIterator -> IO AttrIterator
forall (m :: * -> *) a. Monad m => a -> m a
return
    wrappedPtrFree :: Maybe (GDestroyNotify AttrIterator)
wrappedPtrFree = Maybe (GDestroyNotify AttrIterator)
forall a. Maybe a
Nothing

-- | A convenience alias for `Nothing` :: `Maybe` `AttrIterator`.
noAttrIterator :: Maybe AttrIterator
noAttrIterator :: Maybe AttrIterator
noAttrIterator = Maybe AttrIterator
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AttrIterator
type instance O.AttributeList AttrIterator = AttrIteratorAttributeList
type AttrIteratorAttributeList = ('[ ] :: [(Symbol, *)])
#endif

-- method AttrIterator::destroy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iterator"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrIterator" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoAttrIterator."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_iterator_destroy" pango_attr_iterator_destroy :: 
    Ptr AttrIterator ->                     -- iterator : TInterface (Name {namespace = "Pango", name = "AttrIterator"})
    IO ()

-- | Destroy a t'GI.Pango.Structs.AttrIterator.AttrIterator' and free all associated memory.
attrIteratorDestroy ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrIterator
    -- ^ /@iterator@/: a t'GI.Pango.Structs.AttrIterator.AttrIterator'.
    -> m ()
attrIteratorDestroy :: AttrIterator -> m ()
attrIteratorDestroy iterator :: AttrIterator
iterator = 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 AttrIterator
iterator' <- AttrIterator -> IO (Ptr AttrIterator)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrIterator
iterator
    Ptr AttrIterator -> IO ()
pango_attr_iterator_destroy Ptr AttrIterator
iterator'
    AttrIterator -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrIterator
iterator
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AttrIteratorDestroyMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo AttrIteratorDestroyMethodInfo AttrIterator signature where
    overloadedMethod = attrIteratorDestroy

#endif

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

foreign import ccall "pango_attr_iterator_get_attrs" pango_attr_iterator_get_attrs :: 
    Ptr AttrIterator ->                     -- iterator : TInterface (Name {namespace = "Pango", name = "AttrIterator"})
    IO (Ptr (GSList (Ptr Pango.Attribute.Attribute)))

-- | Gets a list of all attributes at the current position of the
-- iterator.
-- 
-- /Since: 1.2/
attrIteratorGetAttrs ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrIterator
    -- ^ /@iterator@/: a t'GI.Pango.Structs.AttrIterator.AttrIterator'
    -> m [Pango.Attribute.Attribute]
    -- ^ __Returns:__ a list of
    --   all attributes for the current range.
    --   To free this value, call 'GI.Pango.Structs.Attribute.attributeDestroy' on
    --   each value and @/g_slist_free()/@ on the list.
attrIteratorGetAttrs :: AttrIterator -> m [Attribute]
attrIteratorGetAttrs iterator :: AttrIterator
iterator = IO [Attribute] -> m [Attribute]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Attribute] -> m [Attribute])
-> IO [Attribute] -> m [Attribute]
forall a b. (a -> b) -> a -> b
$ do
    Ptr AttrIterator
iterator' <- AttrIterator -> IO (Ptr AttrIterator)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrIterator
iterator
    Ptr (GSList (Ptr Attribute))
result <- Ptr AttrIterator -> IO (Ptr (GSList (Ptr Attribute)))
pango_attr_iterator_get_attrs Ptr AttrIterator
iterator'
    [Ptr Attribute]
result' <- Ptr (GSList (Ptr Attribute)) -> IO [Ptr Attribute]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr Attribute))
result
    [Attribute]
result'' <- (Ptr Attribute -> IO Attribute)
-> [Ptr Attribute] -> IO [Attribute]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr Attribute -> Attribute)
-> Ptr Attribute -> IO Attribute
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) [Ptr Attribute]
result'
    Ptr (GSList (Ptr Attribute)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free Ptr (GSList (Ptr Attribute))
result
    AttrIterator -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrIterator
iterator
    [Attribute] -> IO [Attribute]
forall (m :: * -> *) a. Monad m => a -> m a
return [Attribute]
result''

#if defined(ENABLE_OVERLOADING)
data AttrIteratorGetAttrsMethodInfo
instance (signature ~ (m [Pango.Attribute.Attribute]), MonadIO m) => O.MethodInfo AttrIteratorGetAttrsMethodInfo AttrIterator signature where
    overloadedMethod = attrIteratorGetAttrs

#endif

-- method AttrIterator::get_font
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iterator"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrIterator" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoAttrIterator"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "desc"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "FontDescription" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a #PangoFontDescription to fill in with the current values.\n       The family name in this structure will be set using\n       pango_font_description_set_family_static() using values from\n       an attribute in the #PangoAttrList associated with the iterator,\n       so if you plan to keep it around, you must call:\n       <literal>pango_font_description_set_family (desc, pango_font_description_get_family (desc))</literal>."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "language"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Language" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "if non-%NULL, location to store language tag for item, or %NULL\n           if none is found."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "extra_attrs"
--           , argType =
--               TGSList
--                 (TInterface Name { namespace = "Pango" , name = "Attribute" })
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "if non-%NULL,\n          location in which to store a list of non-font\n          attributes at the the current position; only the highest priority\n          value of each attribute will be added to this list. In order\n          to free this value, you must call pango_attribute_destroy() on\n          each member."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_iterator_get_font" pango_attr_iterator_get_font :: 
    Ptr AttrIterator ->                     -- iterator : TInterface (Name {namespace = "Pango", name = "AttrIterator"})
    Ptr Pango.FontDescription.FontDescription -> -- desc : TInterface (Name {namespace = "Pango", name = "FontDescription"})
    Ptr Pango.Language.Language ->          -- language : TInterface (Name {namespace = "Pango", name = "Language"})
    Ptr (GSList (Ptr Pango.Attribute.Attribute)) -> -- extra_attrs : TGSList (TInterface (Name {namespace = "Pango", name = "Attribute"}))
    IO ()

-- | Get the font and other attributes at the current iterator position.
attrIteratorGetFont ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrIterator
    -- ^ /@iterator@/: a t'GI.Pango.Structs.AttrIterator.AttrIterator'
    -> Pango.FontDescription.FontDescription
    -- ^ /@desc@/: a t'GI.Pango.Structs.FontDescription.FontDescription' to fill in with the current values.
    --        The family name in this structure will be set using
    --        'GI.Pango.Structs.FontDescription.fontDescriptionSetFamilyStatic' using values from
    --        an attribute in the t'GI.Pango.Structs.AttrList.AttrList' associated with the iterator,
    --        so if you plan to keep it around, you must call:
    --        \<literal>pango_font_description_set_family (desc, pango_font_description_get_family (desc))\<\/literal>.
    -> Maybe (Pango.Language.Language)
    -- ^ /@language@/: if non-'P.Nothing', location to store language tag for item, or 'P.Nothing'
    --            if none is found.
    -> [Pango.Attribute.Attribute]
    -- ^ /@extraAttrs@/: if non-'P.Nothing',
    --           location in which to store a list of non-font
    --           attributes at the the current position; only the highest priority
    --           value of each attribute will be added to this list. In order
    --           to free this value, you must call 'GI.Pango.Structs.Attribute.attributeDestroy' on
    --           each member.
    -> m ()
attrIteratorGetFont :: AttrIterator
-> FontDescription -> Maybe Language -> [Attribute] -> m ()
attrIteratorGetFont iterator :: AttrIterator
iterator desc :: FontDescription
desc language :: Maybe Language
language extraAttrs :: [Attribute]
extraAttrs = 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 AttrIterator
iterator' <- AttrIterator -> IO (Ptr AttrIterator)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrIterator
iterator
    Ptr FontDescription
desc' <- FontDescription -> IO (Ptr FontDescription)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontDescription
desc
    Ptr Language
maybeLanguage <- case Maybe Language
language of
        Nothing -> Ptr Language -> IO (Ptr Language)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Language
forall a. Ptr a
nullPtr
        Just jLanguage :: Language
jLanguage -> do
            Ptr Language
jLanguage' <- Language -> IO (Ptr Language)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Language
jLanguage
            Ptr Language -> IO (Ptr Language)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Language
jLanguage'
    [Ptr Attribute]
extraAttrs' <- (Attribute -> IO (Ptr Attribute))
-> [Attribute] -> IO [Ptr Attribute]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM Attribute -> IO (Ptr Attribute)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [Attribute]
extraAttrs
    Ptr (GSList (Ptr Attribute))
extraAttrs'' <- [Ptr Attribute] -> IO (Ptr (GSList (Ptr Attribute)))
forall a. [Ptr a] -> IO (Ptr (GSList (Ptr a)))
packGSList [Ptr Attribute]
extraAttrs'
    Ptr AttrIterator
-> Ptr FontDescription
-> Ptr Language
-> Ptr (GSList (Ptr Attribute))
-> IO ()
pango_attr_iterator_get_font Ptr AttrIterator
iterator' Ptr FontDescription
desc' Ptr Language
maybeLanguage Ptr (GSList (Ptr Attribute))
extraAttrs''
    AttrIterator -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrIterator
iterator
    FontDescription -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr FontDescription
desc
    Maybe Language -> (Language -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Language
language Language -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    (Attribute -> IO ()) -> [Attribute] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ Attribute -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [Attribute]
extraAttrs
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data AttrIteratorGetFontMethodInfo
instance (signature ~ (Pango.FontDescription.FontDescription -> Maybe (Pango.Language.Language) -> [Pango.Attribute.Attribute] -> m ()), MonadIO m) => O.MethodInfo AttrIteratorGetFontMethodInfo AttrIterator signature where
    overloadedMethod = attrIteratorGetFont

#endif

-- method AttrIterator::next
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iterator"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrIterator" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoAttrIterator"
--                 , 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_attr_iterator_next" pango_attr_iterator_next :: 
    Ptr AttrIterator ->                     -- iterator : TInterface (Name {namespace = "Pango", name = "AttrIterator"})
    IO CInt

-- | Advance the iterator until the next change of style.
attrIteratorNext ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrIterator
    -- ^ /@iterator@/: a t'GI.Pango.Structs.AttrIterator.AttrIterator'
    -> m Bool
    -- ^ __Returns:__ 'P.False' if the iterator is at the end of the list, otherwise 'P.True'
attrIteratorNext :: AttrIterator -> m Bool
attrIteratorNext iterator :: AttrIterator
iterator = 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 AttrIterator
iterator' <- AttrIterator -> IO (Ptr AttrIterator)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrIterator
iterator
    CInt
result <- Ptr AttrIterator -> IO CInt
pango_attr_iterator_next Ptr AttrIterator
iterator'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    AttrIterator -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrIterator
iterator
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data AttrIteratorNextMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo AttrIteratorNextMethodInfo AttrIterator signature where
    overloadedMethod = attrIteratorNext

#endif

-- method AttrIterator::range
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "iterator"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrIterator" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoAttrIterator"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the start of the range"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "end"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the end of the range"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_attr_iterator_range" pango_attr_iterator_range :: 
    Ptr AttrIterator ->                     -- iterator : TInterface (Name {namespace = "Pango", name = "AttrIterator"})
    Ptr Int32 ->                            -- start : TBasicType TInt
    Ptr Int32 ->                            -- end : TBasicType TInt
    IO ()

-- | Get the range of the current segment. Note that the
-- stored return values are signed, not unsigned like
-- the values in t'GI.Pango.Structs.Attribute.Attribute'. To deal with this API
-- oversight, stored return values that wouldn\'t fit into
-- a signed integer are clamped to @/G_MAXINT/@.
attrIteratorRange ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    AttrIterator
    -- ^ /@iterator@/: a t'GI.Pango.Structs.AttrIterator.AttrIterator'
    -> m ((Int32, Int32))
attrIteratorRange :: AttrIterator -> m (Int32, Int32)
attrIteratorRange iterator :: AttrIterator
iterator = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr AttrIterator
iterator' <- AttrIterator -> IO (Ptr AttrIterator)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrIterator
iterator
    Ptr Int32
start <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
end <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr AttrIterator -> Ptr Int32 -> Ptr Int32 -> IO ()
pango_attr_iterator_range Ptr AttrIterator
iterator' Ptr Int32
start Ptr Int32
end
    Int32
start' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
start
    Int32
end' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
end
    AttrIterator -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrIterator
iterator
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
start
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
end
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
start', Int32
end')

#if defined(ENABLE_OVERLOADING)
data AttrIteratorRangeMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m) => O.MethodInfo AttrIteratorRangeMethodInfo AttrIterator signature where
    overloadedMethod = attrIteratorRange

#endif

#if defined(ENABLE_OVERLOADING)
type family ResolveAttrIteratorMethod (t :: Symbol) (o :: *) :: * where
    ResolveAttrIteratorMethod "destroy" o = AttrIteratorDestroyMethodInfo
    ResolveAttrIteratorMethod "next" o = AttrIteratorNextMethodInfo
    ResolveAttrIteratorMethod "range" o = AttrIteratorRangeMethodInfo
    ResolveAttrIteratorMethod "getAttrs" o = AttrIteratorGetAttrsMethodInfo
    ResolveAttrIteratorMethod "getFont" o = AttrIteratorGetFontMethodInfo
    ResolveAttrIteratorMethod l o = O.MethodResolutionFailed l o

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

#endif