{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Structs.AttrIterator
(
AttrIterator(..) ,
#if defined(ENABLE_OVERLOADING)
ResolveAttrIteratorMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
AttrIteratorCopyMethodInfo ,
#endif
attrIteratorCopy ,
#if defined(ENABLE_OVERLOADING)
AttrIteratorDestroyMethodInfo ,
#endif
attrIteratorDestroy ,
#if defined(ENABLE_OVERLOADING)
AttrIteratorGetMethodInfo ,
#endif
attrIteratorGet ,
#if defined(ENABLE_OVERLOADING)
AttrIteratorGetAttrsMethodInfo ,
#endif
attrIteratorGetAttrs ,
#if defined(ENABLE_OVERLOADING)
AttrIteratorGetFontMethodInfo ,
#endif
attrIteratorGetFont ,
#if defined(ENABLE_OVERLOADING)
AttrIteratorNextMethodInfo ,
#endif
attrIteratorNext ,
#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
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 Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
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 qualified GHC.Records as R
import {-# SOURCE #-} qualified GI.Pango.Enums as Pango.Enums
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
newtype AttrIterator = AttrIterator (SP.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)
instance SP.ManagedPtrNewtype AttrIterator where
toManagedPtr :: AttrIterator -> ManagedPtr AttrIterator
toManagedPtr (AttrIterator ManagedPtr AttrIterator
p) = ManagedPtr AttrIterator
p
foreign import ccall "pango_attr_iterator_get_type" c_pango_attr_iterator_get_type ::
IO GType
type instance O.ParentTypes AttrIterator = '[]
instance O.HasParentTypes AttrIterator
instance B.Types.TypedObject AttrIterator where
glibType :: IO GType
glibType = IO GType
c_pango_attr_iterator_get_type
instance B.Types.GBoxed AttrIterator
instance B.GValue.IsGValue (Maybe AttrIterator) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_pango_attr_iterator_get_type
gvalueSet_ :: Ptr GValue -> Maybe AttrIterator -> IO ()
gvalueSet_ Ptr GValue
gv Maybe AttrIterator
P.Nothing = Ptr GValue -> Ptr AttrIterator -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr AttrIterator
forall a. Ptr a
FP.nullPtr :: FP.Ptr AttrIterator)
gvalueSet_ Ptr GValue
gv (P.Just AttrIterator
obj) = AttrIterator -> (Ptr AttrIterator -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr AttrIterator
obj (Ptr GValue -> Ptr AttrIterator -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe AttrIterator)
gvalueGet_ Ptr GValue
gv = do
Ptr AttrIterator
ptr <- Ptr GValue -> IO (Ptr AttrIterator)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr AttrIterator)
if Ptr AttrIterator
ptr Ptr AttrIterator -> Ptr AttrIterator -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr AttrIterator
forall a. Ptr a
FP.nullPtr
then AttrIterator -> Maybe AttrIterator
forall a. a -> Maybe a
P.Just (AttrIterator -> Maybe AttrIterator)
-> IO AttrIterator -> IO (Maybe AttrIterator)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr AttrIterator -> AttrIterator)
-> Ptr AttrIterator -> IO AttrIterator
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr AttrIterator -> AttrIterator
AttrIterator Ptr AttrIterator
ptr
else Maybe AttrIterator -> IO (Maybe AttrIterator)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AttrIterator
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList AttrIterator
type instance O.AttributeList AttrIterator = AttrIteratorAttributeList
type AttrIteratorAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "pango_attr_iterator_copy" pango_attr_iterator_copy ::
Ptr AttrIterator ->
IO (Ptr AttrIterator)
attrIteratorCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
AttrIterator
-> m AttrIterator
attrIteratorCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AttrIterator -> m AttrIterator
attrIteratorCopy AttrIterator
iterator = IO AttrIterator -> m AttrIterator
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AttrIterator -> m AttrIterator)
-> IO AttrIterator -> m AttrIterator
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
result <- Ptr AttrIterator -> IO (Ptr AttrIterator)
pango_attr_iterator_copy Ptr AttrIterator
iterator'
Text -> Ptr AttrIterator -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"attrIteratorCopy" Ptr AttrIterator
result
AttrIterator
result' <- ((ManagedPtr AttrIterator -> AttrIterator)
-> Ptr AttrIterator -> IO AttrIterator
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr AttrIterator -> AttrIterator
AttrIterator) Ptr AttrIterator
result
AttrIterator -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrIterator
iterator
AttrIterator -> IO AttrIterator
forall (m :: * -> *) a. Monad m => a -> m a
return AttrIterator
result'
#if defined(ENABLE_OVERLOADING)
data AttrIteratorCopyMethodInfo
instance (signature ~ (m AttrIterator), MonadIO m) => O.OverloadedMethod AttrIteratorCopyMethodInfo AttrIterator signature where
overloadedMethod = attrIteratorCopy
instance O.OverloadedMethodInfo AttrIteratorCopyMethodInfo AttrIterator where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrIterator.attrIteratorCopy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrIterator.html#v:attrIteratorCopy"
})
#endif
foreign import ccall "pango_attr_iterator_destroy" pango_attr_iterator_destroy ::
Ptr AttrIterator ->
IO ()
attrIteratorDestroy ::
(B.CallStack.HasCallStack, MonadIO m) =>
AttrIterator
-> m ()
attrIteratorDestroy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AttrIterator -> m ()
attrIteratorDestroy 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.OverloadedMethod AttrIteratorDestroyMethodInfo AttrIterator signature where
overloadedMethod = attrIteratorDestroy
instance O.OverloadedMethodInfo AttrIteratorDestroyMethodInfo AttrIterator where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrIterator.attrIteratorDestroy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrIterator.html#v:attrIteratorDestroy"
})
#endif
foreign import ccall "pango_attr_iterator_get" pango_attr_iterator_get ::
Ptr AttrIterator ->
CUInt ->
IO (Ptr Pango.Attribute.Attribute)
attrIteratorGet ::
(B.CallStack.HasCallStack, MonadIO m) =>
AttrIterator
-> Pango.Enums.AttrType
-> m (Maybe Pango.Attribute.Attribute)
attrIteratorGet :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AttrIterator -> AttrType -> m (Maybe Attribute)
attrIteratorGet AttrIterator
iterator AttrType
type_ = IO (Maybe Attribute) -> m (Maybe Attribute)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Attribute) -> m (Maybe Attribute))
-> IO (Maybe Attribute) -> m (Maybe 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
let type_' :: CUInt
type_' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (AttrType -> Int) -> AttrType -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AttrType -> Int
forall a. Enum a => a -> Int
fromEnum) AttrType
type_
Ptr Attribute
result <- Ptr AttrIterator -> CUInt -> IO (Ptr Attribute)
pango_attr_iterator_get Ptr AttrIterator
iterator' CUInt
type_'
Maybe Attribute
maybeResult <- Ptr Attribute
-> (Ptr Attribute -> IO Attribute) -> IO (Maybe Attribute)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Attribute
result ((Ptr Attribute -> IO Attribute) -> IO (Maybe Attribute))
-> (Ptr Attribute -> IO Attribute) -> IO (Maybe Attribute)
forall a b. (a -> b) -> a -> b
$ \Ptr Attribute
result' -> do
Attribute
result'' <- ((ManagedPtr Attribute -> Attribute)
-> Ptr Attribute -> IO Attribute
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) Ptr Attribute
result'
Attribute -> IO Attribute
forall (m :: * -> *) a. Monad m => a -> m a
return Attribute
result''
AttrIterator -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr AttrIterator
iterator
Maybe Attribute -> IO (Maybe Attribute)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Attribute
maybeResult
#if defined(ENABLE_OVERLOADING)
data AttrIteratorGetMethodInfo
instance (signature ~ (Pango.Enums.AttrType -> m (Maybe Pango.Attribute.Attribute)), MonadIO m) => O.OverloadedMethod AttrIteratorGetMethodInfo AttrIterator signature where
overloadedMethod = attrIteratorGet
instance O.OverloadedMethodInfo AttrIteratorGetMethodInfo AttrIterator where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrIterator.attrIteratorGet",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrIterator.html#v:attrIteratorGet"
})
#endif
foreign import ccall "pango_attr_iterator_get_attrs" pango_attr_iterator_get_attrs ::
Ptr AttrIterator ->
IO (Ptr (GSList (Ptr Pango.Attribute.Attribute)))
attrIteratorGetAttrs ::
(B.CallStack.HasCallStack, MonadIO m) =>
AttrIterator
-> m [Pango.Attribute.Attribute]
attrIteratorGetAttrs :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AttrIterator -> m [Attribute]
attrIteratorGetAttrs 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, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed 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.OverloadedMethod AttrIteratorGetAttrsMethodInfo AttrIterator signature where
overloadedMethod = attrIteratorGetAttrs
instance O.OverloadedMethodInfo AttrIteratorGetAttrsMethodInfo AttrIterator where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrIterator.attrIteratorGetAttrs",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrIterator.html#v:attrIteratorGetAttrs"
})
#endif
foreign import ccall "pango_attr_iterator_get_font" pango_attr_iterator_get_font ::
Ptr AttrIterator ->
Ptr Pango.FontDescription.FontDescription ->
Ptr (Ptr Pango.Language.Language) ->
Ptr (Ptr (GSList (Ptr Pango.Attribute.Attribute))) ->
IO ()
attrIteratorGetFont ::
(B.CallStack.HasCallStack, MonadIO m) =>
AttrIterator
-> Pango.FontDescription.FontDescription
-> m ((Maybe Pango.Language.Language, [Pango.Attribute.Attribute]))
attrIteratorGetFont :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AttrIterator -> FontDescription -> m (Maybe Language, [Attribute])
attrIteratorGetFont AttrIterator
iterator FontDescription
desc = IO (Maybe Language, [Attribute]) -> m (Maybe Language, [Attribute])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Language, [Attribute])
-> m (Maybe Language, [Attribute]))
-> IO (Maybe Language, [Attribute])
-> m (Maybe Language, [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 FontDescription
desc' <- FontDescription -> IO (Ptr FontDescription)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontDescription
desc
Ptr (Ptr Language)
language <- IO (Ptr (Ptr Language))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Pango.Language.Language))
Ptr (Ptr (GSList (Ptr Attribute)))
extraAttrs <- IO (Ptr (Ptr (GSList (Ptr Attribute))))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr (GSList (Ptr Pango.Attribute.Attribute))))
Ptr AttrIterator
-> Ptr FontDescription
-> Ptr (Ptr Language)
-> Ptr (Ptr (GSList (Ptr Attribute)))
-> IO ()
pango_attr_iterator_get_font Ptr AttrIterator
iterator' Ptr FontDescription
desc' Ptr (Ptr Language)
language Ptr (Ptr (GSList (Ptr Attribute)))
extraAttrs
Ptr Language
language' <- Ptr (Ptr Language) -> IO (Ptr Language)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Language)
language
Maybe Language
maybeLanguage' <- Ptr Language
-> (Ptr Language -> IO Language) -> IO (Maybe Language)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Language
language' ((Ptr Language -> IO Language) -> IO (Maybe Language))
-> (Ptr Language -> IO Language) -> IO (Maybe Language)
forall a b. (a -> b) -> a -> b
$ \Ptr Language
language'' -> do
Language
language''' <- ((ManagedPtr Language -> Language) -> Ptr Language -> IO Language
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Language -> Language
Pango.Language.Language) Ptr Language
language''
Language -> IO Language
forall (m :: * -> *) a. Monad m => a -> m a
return Language
language'''
Ptr (GSList (Ptr Attribute))
extraAttrs' <- Ptr (Ptr (GSList (Ptr Attribute)))
-> IO (Ptr (GSList (Ptr Attribute)))
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr (GSList (Ptr Attribute)))
extraAttrs
[Ptr Attribute]
extraAttrs'' <- Ptr (GSList (Ptr Attribute)) -> IO [Ptr Attribute]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr Attribute))
extraAttrs'
[Attribute]
extraAttrs''' <- (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, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Attribute -> Attribute
Pango.Attribute.Attribute) [Ptr Attribute]
extraAttrs''
Ptr (GSList (Ptr Attribute)) -> IO ()
forall a. Ptr (GSList a) -> IO ()
g_slist_free 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
Ptr (Ptr Language) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Language)
language
Ptr (Ptr (GSList (Ptr Attribute))) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr (GSList (Ptr Attribute)))
extraAttrs
(Maybe Language, [Attribute]) -> IO (Maybe Language, [Attribute])
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Language
maybeLanguage', [Attribute]
extraAttrs''')
#if defined(ENABLE_OVERLOADING)
data AttrIteratorGetFontMethodInfo
instance (signature ~ (Pango.FontDescription.FontDescription -> m ((Maybe Pango.Language.Language, [Pango.Attribute.Attribute]))), MonadIO m) => O.OverloadedMethod AttrIteratorGetFontMethodInfo AttrIterator signature where
overloadedMethod = attrIteratorGetFont
instance O.OverloadedMethodInfo AttrIteratorGetFontMethodInfo AttrIterator where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrIterator.attrIteratorGetFont",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrIterator.html#v:attrIteratorGetFont"
})
#endif
foreign import ccall "pango_attr_iterator_next" pango_attr_iterator_next ::
Ptr AttrIterator ->
IO CInt
attrIteratorNext ::
(B.CallStack.HasCallStack, MonadIO m) =>
AttrIterator
-> m Bool
attrIteratorNext :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AttrIterator -> m Bool
attrIteratorNext 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
/= CInt
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.OverloadedMethod AttrIteratorNextMethodInfo AttrIterator signature where
overloadedMethod = attrIteratorNext
instance O.OverloadedMethodInfo AttrIteratorNextMethodInfo AttrIterator where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrIterator.attrIteratorNext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrIterator.html#v:attrIteratorNext"
})
#endif
foreign import ccall "pango_attr_iterator_range" pango_attr_iterator_range ::
Ptr AttrIterator ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
attrIteratorRange ::
(B.CallStack.HasCallStack, MonadIO m) =>
AttrIterator
-> m ((Int32, Int32))
attrIteratorRange :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
AttrIterator -> m (Int32, Int32)
attrIteratorRange 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.OverloadedMethod AttrIteratorRangeMethodInfo AttrIterator signature where
overloadedMethod = attrIteratorRange
instance O.OverloadedMethodInfo AttrIteratorRangeMethodInfo AttrIterator where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Pango.Structs.AttrIterator.attrIteratorRange",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Structs-AttrIterator.html#v:attrIteratorRange"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveAttrIteratorMethod (t :: Symbol) (o :: *) :: * where
ResolveAttrIteratorMethod "copy" o = AttrIteratorCopyMethodInfo
ResolveAttrIteratorMethod "destroy" o = AttrIteratorDestroyMethodInfo
ResolveAttrIteratorMethod "get" o = AttrIteratorGetMethodInfo
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.OverloadedMethod 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
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveAttrIteratorMethod t AttrIterator, O.OverloadedMethod info AttrIterator p, R.HasField t AttrIterator p) => R.HasField t AttrIterator p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveAttrIteratorMethod t AttrIterator, O.OverloadedMethodInfo info AttrIterator) => OL.IsLabel t (O.MethodProxy info AttrIterator) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif