{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Structs.LayoutIter
(
LayoutIter(..) ,
noLayoutIter ,
#if defined(ENABLE_OVERLOADING)
ResolveLayoutIterMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
LayoutIterAtLastLineMethodInfo ,
#endif
layoutIterAtLastLine ,
#if defined(ENABLE_OVERLOADING)
LayoutIterCopyMethodInfo ,
#endif
layoutIterCopy ,
#if defined(ENABLE_OVERLOADING)
LayoutIterFreeMethodInfo ,
#endif
layoutIterFree ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetBaselineMethodInfo ,
#endif
layoutIterGetBaseline ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetCharExtentsMethodInfo ,
#endif
layoutIterGetCharExtents ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetClusterExtentsMethodInfo ,
#endif
layoutIterGetClusterExtents ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetIndexMethodInfo ,
#endif
layoutIterGetIndex ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetLayoutMethodInfo ,
#endif
layoutIterGetLayout ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetLayoutExtentsMethodInfo ,
#endif
layoutIterGetLayoutExtents ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetLineMethodInfo ,
#endif
layoutIterGetLine ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetLineExtentsMethodInfo ,
#endif
layoutIterGetLineExtents ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetLineReadonlyMethodInfo ,
#endif
layoutIterGetLineReadonly ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetLineYrangeMethodInfo ,
#endif
layoutIterGetLineYrange ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetRunMethodInfo ,
#endif
layoutIterGetRun ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetRunExtentsMethodInfo ,
#endif
layoutIterGetRunExtents ,
#if defined(ENABLE_OVERLOADING)
LayoutIterGetRunReadonlyMethodInfo ,
#endif
layoutIterGetRunReadonly ,
#if defined(ENABLE_OVERLOADING)
LayoutIterNextCharMethodInfo ,
#endif
layoutIterNextChar ,
#if defined(ENABLE_OVERLOADING)
LayoutIterNextClusterMethodInfo ,
#endif
layoutIterNextCluster ,
#if defined(ENABLE_OVERLOADING)
LayoutIterNextLineMethodInfo ,
#endif
layoutIterNextLine ,
#if defined(ENABLE_OVERLOADING)
LayoutIterNextRunMethodInfo ,
#endif
layoutIterNextRun ,
) 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.Objects.Layout as Pango.Layout
import {-# SOURCE #-} qualified GI.Pango.Structs.GlyphItem as Pango.GlyphItem
import {-# SOURCE #-} qualified GI.Pango.Structs.LayoutLine as Pango.LayoutLine
import {-# SOURCE #-} qualified GI.Pango.Structs.Rectangle as Pango.Rectangle
newtype LayoutIter = LayoutIter (ManagedPtr LayoutIter)
deriving (LayoutIter -> LayoutIter -> Bool
(LayoutIter -> LayoutIter -> Bool)
-> (LayoutIter -> LayoutIter -> Bool) -> Eq LayoutIter
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LayoutIter -> LayoutIter -> Bool
$c/= :: LayoutIter -> LayoutIter -> Bool
== :: LayoutIter -> LayoutIter -> Bool
$c== :: LayoutIter -> LayoutIter -> Bool
Eq)
foreign import ccall "pango_layout_iter_get_type" c_pango_layout_iter_get_type ::
IO GType
instance BoxedObject LayoutIter where
boxedType :: LayoutIter -> IO GType
boxedType _ = IO GType
c_pango_layout_iter_get_type
instance B.GValue.IsGValue LayoutIter where
toGValue :: LayoutIter -> IO GValue
toGValue o :: LayoutIter
o = do
GType
gtype <- IO GType
c_pango_layout_iter_get_type
LayoutIter -> (Ptr LayoutIter -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr LayoutIter
o (GType
-> (GValue -> Ptr LayoutIter -> IO ())
-> Ptr LayoutIter
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr LayoutIter -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO LayoutIter
fromGValue gv :: GValue
gv = do
Ptr LayoutIter
ptr <- GValue -> IO (Ptr LayoutIter)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr LayoutIter)
(ManagedPtr LayoutIter -> LayoutIter)
-> Ptr LayoutIter -> IO LayoutIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr LayoutIter -> LayoutIter
LayoutIter Ptr LayoutIter
ptr
noLayoutIter :: Maybe LayoutIter
noLayoutIter :: Maybe LayoutIter
noLayoutIter = Maybe LayoutIter
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList LayoutIter
type instance O.AttributeList LayoutIter = LayoutIterAttributeList
type LayoutIterAttributeList = ('[ ] :: [(Symbol, *)])
#endif
foreign import ccall "pango_layout_iter_at_last_line" pango_layout_iter_at_last_line ::
Ptr LayoutIter ->
IO CInt
layoutIterAtLastLine ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Bool
layoutIterAtLastLine :: LayoutIter -> m Bool
layoutIterAtLastLine iter :: LayoutIter
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 LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
CInt
result <- Ptr LayoutIter -> IO CInt
pango_layout_iter_at_last_line Ptr LayoutIter
iter'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LayoutIterAtLastLineMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo LayoutIterAtLastLineMethodInfo LayoutIter signature where
overloadedMethod = layoutIterAtLastLine
#endif
foreign import ccall "pango_layout_iter_copy" pango_layout_iter_copy ::
Ptr LayoutIter ->
IO (Ptr LayoutIter)
layoutIterCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m (Maybe LayoutIter)
layoutIterCopy :: LayoutIter -> m (Maybe LayoutIter)
layoutIterCopy iter :: LayoutIter
iter = IO (Maybe LayoutIter) -> m (Maybe LayoutIter)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe LayoutIter) -> m (Maybe LayoutIter))
-> IO (Maybe LayoutIter) -> m (Maybe LayoutIter)
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr LayoutIter
result <- Ptr LayoutIter -> IO (Ptr LayoutIter)
pango_layout_iter_copy Ptr LayoutIter
iter'
Maybe LayoutIter
maybeResult <- Ptr LayoutIter
-> (Ptr LayoutIter -> IO LayoutIter) -> IO (Maybe LayoutIter)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr LayoutIter
result ((Ptr LayoutIter -> IO LayoutIter) -> IO (Maybe LayoutIter))
-> (Ptr LayoutIter -> IO LayoutIter) -> IO (Maybe LayoutIter)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr LayoutIter
result' -> do
LayoutIter
result'' <- ((ManagedPtr LayoutIter -> LayoutIter)
-> Ptr LayoutIter -> IO LayoutIter
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr LayoutIter -> LayoutIter
LayoutIter) Ptr LayoutIter
result'
LayoutIter -> IO LayoutIter
forall (m :: * -> *) a. Monad m => a -> m a
return LayoutIter
result''
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Maybe LayoutIter -> IO (Maybe LayoutIter)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LayoutIter
maybeResult
#if defined(ENABLE_OVERLOADING)
data LayoutIterCopyMethodInfo
instance (signature ~ (m (Maybe LayoutIter)), MonadIO m) => O.MethodInfo LayoutIterCopyMethodInfo LayoutIter signature where
overloadedMethod = layoutIterCopy
#endif
foreign import ccall "pango_layout_iter_free" pango_layout_iter_free ::
Ptr LayoutIter ->
IO ()
layoutIterFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m ()
layoutIterFree :: LayoutIter -> m ()
layoutIterFree iter :: LayoutIter
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 LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr LayoutIter -> IO ()
pango_layout_iter_free Ptr LayoutIter
iter'
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LayoutIterFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo LayoutIterFreeMethodInfo LayoutIter signature where
overloadedMethod = layoutIterFree
#endif
foreign import ccall "pango_layout_iter_get_baseline" pango_layout_iter_get_baseline ::
Ptr LayoutIter ->
IO Int32
layoutIterGetBaseline ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Int32
layoutIterGetBaseline :: LayoutIter -> m Int32
layoutIterGetBaseline iter :: LayoutIter
iter = 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
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Int32
result <- Ptr LayoutIter -> IO Int32
pango_layout_iter_get_baseline Ptr LayoutIter
iter'
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetBaselineMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo LayoutIterGetBaselineMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetBaseline
#endif
foreign import ccall "pango_layout_iter_get_char_extents" pango_layout_iter_get_char_extents ::
Ptr LayoutIter ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutIterGetCharExtents ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m (Pango.Rectangle.Rectangle)
layoutIterGetCharExtents :: LayoutIter -> m Rectangle
layoutIterGetCharExtents iter :: LayoutIter
iter = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr Rectangle
logicalRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr LayoutIter -> Ptr Rectangle -> IO ()
pango_layout_iter_get_char_extents Ptr LayoutIter
iter' Ptr Rectangle
logicalRect
Rectangle
logicalRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
logicalRect
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
logicalRect'
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetCharExtentsMethodInfo
instance (signature ~ (m (Pango.Rectangle.Rectangle)), MonadIO m) => O.MethodInfo LayoutIterGetCharExtentsMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetCharExtents
#endif
foreign import ccall "pango_layout_iter_get_cluster_extents" pango_layout_iter_get_cluster_extents ::
Ptr LayoutIter ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutIterGetClusterExtents ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutIterGetClusterExtents :: LayoutIter -> m (Rectangle, Rectangle)
layoutIterGetClusterExtents iter :: LayoutIter
iter = IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr Rectangle
inkRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr Rectangle
logicalRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr LayoutIter -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_iter_get_cluster_extents Ptr LayoutIter
iter' Ptr Rectangle
inkRect Ptr Rectangle
logicalRect
Rectangle
inkRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
inkRect
Rectangle
logicalRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
logicalRect
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
(Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
inkRect', Rectangle
logicalRect')
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetClusterExtentsMethodInfo
instance (signature ~ (m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m) => O.MethodInfo LayoutIterGetClusterExtentsMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetClusterExtents
#endif
foreign import ccall "pango_layout_iter_get_index" pango_layout_iter_get_index ::
Ptr LayoutIter ->
IO Int32
layoutIterGetIndex ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Int32
layoutIterGetIndex :: LayoutIter -> m Int32
layoutIterGetIndex iter :: LayoutIter
iter = 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
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Int32
result <- Ptr LayoutIter -> IO Int32
pango_layout_iter_get_index Ptr LayoutIter
iter'
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetIndexMethodInfo
instance (signature ~ (m Int32), MonadIO m) => O.MethodInfo LayoutIterGetIndexMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetIndex
#endif
foreign import ccall "pango_layout_iter_get_layout" pango_layout_iter_get_layout ::
Ptr LayoutIter ->
IO (Ptr Pango.Layout.Layout)
layoutIterGetLayout ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Pango.Layout.Layout
layoutIterGetLayout :: LayoutIter -> m Layout
layoutIterGetLayout iter :: LayoutIter
iter = IO Layout -> m Layout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Layout -> m Layout) -> IO Layout -> m Layout
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr Layout
result <- Ptr LayoutIter -> IO (Ptr Layout)
pango_layout_iter_get_layout Ptr LayoutIter
iter'
Text -> Ptr Layout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "layoutIterGetLayout" Ptr Layout
result
Layout
result' <- ((ManagedPtr Layout -> Layout) -> Ptr Layout -> IO Layout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Layout -> Layout
Pango.Layout.Layout) Ptr Layout
result
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Layout -> IO Layout
forall (m :: * -> *) a. Monad m => a -> m a
return Layout
result'
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetLayoutMethodInfo
instance (signature ~ (m Pango.Layout.Layout), MonadIO m) => O.MethodInfo LayoutIterGetLayoutMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetLayout
#endif
foreign import ccall "pango_layout_iter_get_layout_extents" pango_layout_iter_get_layout_extents ::
Ptr LayoutIter ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutIterGetLayoutExtents ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutIterGetLayoutExtents :: LayoutIter -> m (Rectangle, Rectangle)
layoutIterGetLayoutExtents iter :: LayoutIter
iter = IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr Rectangle
inkRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr Rectangle
logicalRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr LayoutIter -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_iter_get_layout_extents Ptr LayoutIter
iter' Ptr Rectangle
inkRect Ptr Rectangle
logicalRect
Rectangle
inkRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
inkRect
Rectangle
logicalRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
logicalRect
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
(Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
inkRect', Rectangle
logicalRect')
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetLayoutExtentsMethodInfo
instance (signature ~ (m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m) => O.MethodInfo LayoutIterGetLayoutExtentsMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetLayoutExtents
#endif
foreign import ccall "pango_layout_iter_get_line" pango_layout_iter_get_line ::
Ptr LayoutIter ->
IO (Ptr Pango.LayoutLine.LayoutLine)
layoutIterGetLine ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Pango.LayoutLine.LayoutLine
layoutIterGetLine :: LayoutIter -> m LayoutLine
layoutIterGetLine iter :: LayoutIter
iter = IO LayoutLine -> m LayoutLine
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LayoutLine -> m LayoutLine) -> IO LayoutLine -> m LayoutLine
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr LayoutLine
result <- Ptr LayoutIter -> IO (Ptr LayoutLine)
pango_layout_iter_get_line Ptr LayoutIter
iter'
Text -> Ptr LayoutLine -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "layoutIterGetLine" Ptr LayoutLine
result
LayoutLine
result' <- ((ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr LayoutLine -> LayoutLine
Pango.LayoutLine.LayoutLine) Ptr LayoutLine
result
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
LayoutLine -> IO LayoutLine
forall (m :: * -> *) a. Monad m => a -> m a
return LayoutLine
result'
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetLineMethodInfo
instance (signature ~ (m Pango.LayoutLine.LayoutLine), MonadIO m) => O.MethodInfo LayoutIterGetLineMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetLine
#endif
foreign import ccall "pango_layout_iter_get_line_extents" pango_layout_iter_get_line_extents ::
Ptr LayoutIter ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutIterGetLineExtents ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutIterGetLineExtents :: LayoutIter -> m (Rectangle, Rectangle)
layoutIterGetLineExtents iter :: LayoutIter
iter = IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr Rectangle
inkRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr Rectangle
logicalRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr LayoutIter -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_iter_get_line_extents Ptr LayoutIter
iter' Ptr Rectangle
inkRect Ptr Rectangle
logicalRect
Rectangle
inkRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
inkRect
Rectangle
logicalRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
logicalRect
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
(Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
inkRect', Rectangle
logicalRect')
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetLineExtentsMethodInfo
instance (signature ~ (m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m) => O.MethodInfo LayoutIterGetLineExtentsMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetLineExtents
#endif
foreign import ccall "pango_layout_iter_get_line_readonly" pango_layout_iter_get_line_readonly ::
Ptr LayoutIter ->
IO (Ptr Pango.LayoutLine.LayoutLine)
layoutIterGetLineReadonly ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Pango.LayoutLine.LayoutLine
layoutIterGetLineReadonly :: LayoutIter -> m LayoutLine
layoutIterGetLineReadonly iter :: LayoutIter
iter = IO LayoutLine -> m LayoutLine
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LayoutLine -> m LayoutLine) -> IO LayoutLine -> m LayoutLine
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr LayoutLine
result <- Ptr LayoutIter -> IO (Ptr LayoutLine)
pango_layout_iter_get_line_readonly Ptr LayoutIter
iter'
Text -> Ptr LayoutLine -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "layoutIterGetLineReadonly" Ptr LayoutLine
result
LayoutLine
result' <- ((ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr LayoutLine -> LayoutLine
Pango.LayoutLine.LayoutLine) Ptr LayoutLine
result
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
LayoutLine -> IO LayoutLine
forall (m :: * -> *) a. Monad m => a -> m a
return LayoutLine
result'
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetLineReadonlyMethodInfo
instance (signature ~ (m Pango.LayoutLine.LayoutLine), MonadIO m) => O.MethodInfo LayoutIterGetLineReadonlyMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetLineReadonly
#endif
foreign import ccall "pango_layout_iter_get_line_yrange" pango_layout_iter_get_line_yrange ::
Ptr LayoutIter ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
layoutIterGetLineYrange ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m ((Int32, Int32))
layoutIterGetLineYrange :: LayoutIter -> m (Int32, Int32)
layoutIterGetLineYrange iter :: LayoutIter
iter = 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 LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr Int32
y0_ <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr Int32
y1_ <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr LayoutIter -> Ptr Int32 -> Ptr Int32 -> IO ()
pango_layout_iter_get_line_yrange Ptr LayoutIter
iter' Ptr Int32
y0_ Ptr Int32
y1_
Int32
y0_' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y0_
Int32
y1_' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
y1_
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y0_
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
y1_
(Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
y0_', Int32
y1_')
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetLineYrangeMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m) => O.MethodInfo LayoutIterGetLineYrangeMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetLineYrange
#endif
foreign import ccall "pango_layout_iter_get_run" pango_layout_iter_get_run ::
Ptr LayoutIter ->
IO (Ptr Pango.GlyphItem.GlyphItem)
layoutIterGetRun ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m (Maybe Pango.GlyphItem.GlyphItem)
layoutIterGetRun :: LayoutIter -> m (Maybe GlyphItem)
layoutIterGetRun iter :: LayoutIter
iter = 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
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr GlyphItem
result <- Ptr LayoutIter -> IO (Ptr GlyphItem)
pango_layout_iter_get_run Ptr LayoutIter
iter'
Maybe GlyphItem
maybeResult <- Ptr GlyphItem
-> (Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GlyphItem
result ((Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem))
-> (Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GlyphItem
result' -> do
GlyphItem
result'' <- ((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
result'
GlyphItem -> IO GlyphItem
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphItem
result''
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Maybe GlyphItem -> IO (Maybe GlyphItem)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GlyphItem
maybeResult
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetRunMethodInfo
instance (signature ~ (m (Maybe Pango.GlyphItem.GlyphItem)), MonadIO m) => O.MethodInfo LayoutIterGetRunMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetRun
#endif
foreign import ccall "pango_layout_iter_get_run_extents" pango_layout_iter_get_run_extents ::
Ptr LayoutIter ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutIterGetRunExtents ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutIterGetRunExtents :: LayoutIter -> m (Rectangle, Rectangle)
layoutIterGetRunExtents iter :: LayoutIter
iter = IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle))
-> IO (Rectangle, Rectangle) -> m (Rectangle, Rectangle)
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr Rectangle
inkRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr Rectangle
logicalRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
callocBytes 16 :: IO (Ptr Pango.Rectangle.Rectangle)
Ptr LayoutIter -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_iter_get_run_extents Ptr LayoutIter
iter' Ptr Rectangle
inkRect Ptr Rectangle
logicalRect
Rectangle
inkRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
inkRect
Rectangle
logicalRect' <- ((ManagedPtr Rectangle -> Rectangle)
-> Ptr Rectangle -> IO Rectangle
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr Rectangle -> Rectangle
Pango.Rectangle.Rectangle) Ptr Rectangle
logicalRect
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
(Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
inkRect', Rectangle
logicalRect')
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetRunExtentsMethodInfo
instance (signature ~ (m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m) => O.MethodInfo LayoutIterGetRunExtentsMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetRunExtents
#endif
foreign import ccall "pango_layout_iter_get_run_readonly" pango_layout_iter_get_run_readonly ::
Ptr LayoutIter ->
IO (Ptr Pango.GlyphItem.GlyphItem)
layoutIterGetRunReadonly ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m (Maybe Pango.GlyphItem.GlyphItem)
layoutIterGetRunReadonly :: LayoutIter -> m (Maybe GlyphItem)
layoutIterGetRunReadonly iter :: LayoutIter
iter = 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
$ do
Ptr LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
Ptr GlyphItem
result <- Ptr LayoutIter -> IO (Ptr GlyphItem)
pango_layout_iter_get_run_readonly Ptr LayoutIter
iter'
Maybe GlyphItem
maybeResult <- Ptr GlyphItem
-> (Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GlyphItem
result ((Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem))
-> (Ptr GlyphItem -> IO GlyphItem) -> IO (Maybe GlyphItem)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr GlyphItem
result' -> do
GlyphItem
result'' <- ((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
result'
GlyphItem -> IO GlyphItem
forall (m :: * -> *) a. Monad m => a -> m a
return GlyphItem
result''
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Maybe GlyphItem -> IO (Maybe GlyphItem)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GlyphItem
maybeResult
#if defined(ENABLE_OVERLOADING)
data LayoutIterGetRunReadonlyMethodInfo
instance (signature ~ (m (Maybe Pango.GlyphItem.GlyphItem)), MonadIO m) => O.MethodInfo LayoutIterGetRunReadonlyMethodInfo LayoutIter signature where
overloadedMethod = layoutIterGetRunReadonly
#endif
foreign import ccall "pango_layout_iter_next_char" pango_layout_iter_next_char ::
Ptr LayoutIter ->
IO CInt
layoutIterNextChar ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Bool
layoutIterNextChar :: LayoutIter -> m Bool
layoutIterNextChar iter :: LayoutIter
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 LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
CInt
result <- Ptr LayoutIter -> IO CInt
pango_layout_iter_next_char Ptr LayoutIter
iter'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LayoutIterNextCharMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo LayoutIterNextCharMethodInfo LayoutIter signature where
overloadedMethod = layoutIterNextChar
#endif
foreign import ccall "pango_layout_iter_next_cluster" pango_layout_iter_next_cluster ::
Ptr LayoutIter ->
IO CInt
layoutIterNextCluster ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Bool
layoutIterNextCluster :: LayoutIter -> m Bool
layoutIterNextCluster iter :: LayoutIter
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 LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
CInt
result <- Ptr LayoutIter -> IO CInt
pango_layout_iter_next_cluster Ptr LayoutIter
iter'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LayoutIterNextClusterMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo LayoutIterNextClusterMethodInfo LayoutIter signature where
overloadedMethod = layoutIterNextCluster
#endif
foreign import ccall "pango_layout_iter_next_line" pango_layout_iter_next_line ::
Ptr LayoutIter ->
IO CInt
layoutIterNextLine ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Bool
layoutIterNextLine :: LayoutIter -> m Bool
layoutIterNextLine iter :: LayoutIter
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 LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
CInt
result <- Ptr LayoutIter -> IO CInt
pango_layout_iter_next_line Ptr LayoutIter
iter'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LayoutIterNextLineMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo LayoutIterNextLineMethodInfo LayoutIter signature where
overloadedMethod = layoutIterNextLine
#endif
foreign import ccall "pango_layout_iter_next_run" pango_layout_iter_next_run ::
Ptr LayoutIter ->
IO CInt
layoutIterNextRun ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutIter
-> m Bool
layoutIterNextRun :: LayoutIter -> m Bool
layoutIterNextRun iter :: LayoutIter
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 LayoutIter
iter' <- LayoutIter -> IO (Ptr LayoutIter)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutIter
iter
CInt
result <- Ptr LayoutIter -> IO CInt
pango_layout_iter_next_run Ptr LayoutIter
iter'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
LayoutIter -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutIter
iter
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data LayoutIterNextRunMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.MethodInfo LayoutIterNextRunMethodInfo LayoutIter signature where
overloadedMethod = layoutIterNextRun
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveLayoutIterMethod (t :: Symbol) (o :: *) :: * where
ResolveLayoutIterMethod "atLastLine" o = LayoutIterAtLastLineMethodInfo
ResolveLayoutIterMethod "copy" o = LayoutIterCopyMethodInfo
ResolveLayoutIterMethod "free" o = LayoutIterFreeMethodInfo
ResolveLayoutIterMethod "nextChar" o = LayoutIterNextCharMethodInfo
ResolveLayoutIterMethod "nextCluster" o = LayoutIterNextClusterMethodInfo
ResolveLayoutIterMethod "nextLine" o = LayoutIterNextLineMethodInfo
ResolveLayoutIterMethod "nextRun" o = LayoutIterNextRunMethodInfo
ResolveLayoutIterMethod "getBaseline" o = LayoutIterGetBaselineMethodInfo
ResolveLayoutIterMethod "getCharExtents" o = LayoutIterGetCharExtentsMethodInfo
ResolveLayoutIterMethod "getClusterExtents" o = LayoutIterGetClusterExtentsMethodInfo
ResolveLayoutIterMethod "getIndex" o = LayoutIterGetIndexMethodInfo
ResolveLayoutIterMethod "getLayout" o = LayoutIterGetLayoutMethodInfo
ResolveLayoutIterMethod "getLayoutExtents" o = LayoutIterGetLayoutExtentsMethodInfo
ResolveLayoutIterMethod "getLine" o = LayoutIterGetLineMethodInfo
ResolveLayoutIterMethod "getLineExtents" o = LayoutIterGetLineExtentsMethodInfo
ResolveLayoutIterMethod "getLineReadonly" o = LayoutIterGetLineReadonlyMethodInfo
ResolveLayoutIterMethod "getLineYrange" o = LayoutIterGetLineYrangeMethodInfo
ResolveLayoutIterMethod "getRun" o = LayoutIterGetRunMethodInfo
ResolveLayoutIterMethod "getRunExtents" o = LayoutIterGetRunExtentsMethodInfo
ResolveLayoutIterMethod "getRunReadonly" o = LayoutIterGetRunReadonlyMethodInfo
ResolveLayoutIterMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveLayoutIterMethod t LayoutIter, O.MethodInfo info LayoutIter p) => OL.IsLabel t (LayoutIter -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif