{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Pango.Structs.LayoutLine
(
LayoutLine(..) ,
newZeroLayoutLine ,
noLayoutLine ,
#if defined(ENABLE_OVERLOADING)
ResolveLayoutLineMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
LayoutLineGetExtentsMethodInfo ,
#endif
layoutLineGetExtents ,
#if defined(ENABLE_OVERLOADING)
LayoutLineGetPixelExtentsMethodInfo ,
#endif
layoutLineGetPixelExtents ,
#if defined(ENABLE_OVERLOADING)
LayoutLineGetXRangesMethodInfo ,
#endif
layoutLineGetXRanges ,
#if defined(ENABLE_OVERLOADING)
LayoutLineIndexToXMethodInfo ,
#endif
layoutLineIndexToX ,
#if defined(ENABLE_OVERLOADING)
LayoutLineRefMethodInfo ,
#endif
layoutLineRef ,
#if defined(ENABLE_OVERLOADING)
LayoutLineUnrefMethodInfo ,
#endif
layoutLineUnref ,
#if defined(ENABLE_OVERLOADING)
LayoutLineXToIndexMethodInfo ,
#endif
layoutLineXToIndex ,
getLayoutLineIsParagraphStart ,
#if defined(ENABLE_OVERLOADING)
layoutLine_isParagraphStart ,
#endif
setLayoutLineIsParagraphStart ,
clearLayoutLineLayout ,
getLayoutLineLayout ,
#if defined(ENABLE_OVERLOADING)
layoutLine_layout ,
#endif
setLayoutLineLayout ,
getLayoutLineLength ,
#if defined(ENABLE_OVERLOADING)
layoutLine_length ,
#endif
setLayoutLineLength ,
getLayoutLineResolvedDir ,
#if defined(ENABLE_OVERLOADING)
layoutLine_resolvedDir ,
#endif
setLayoutLineResolvedDir ,
clearLayoutLineRuns ,
getLayoutLineRuns ,
#if defined(ENABLE_OVERLOADING)
layoutLine_runs ,
#endif
setLayoutLineRuns ,
getLayoutLineStartIndex ,
#if defined(ENABLE_OVERLOADING)
layoutLine_startIndex ,
#endif
setLayoutLineStartIndex ,
) 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.Rectangle as Pango.Rectangle
newtype LayoutLine = LayoutLine (ManagedPtr LayoutLine)
deriving (LayoutLine -> LayoutLine -> Bool
(LayoutLine -> LayoutLine -> Bool)
-> (LayoutLine -> LayoutLine -> Bool) -> Eq LayoutLine
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LayoutLine -> LayoutLine -> Bool
$c/= :: LayoutLine -> LayoutLine -> Bool
== :: LayoutLine -> LayoutLine -> Bool
$c== :: LayoutLine -> LayoutLine -> Bool
Eq)
foreign import ccall "pango_layout_line_get_type" c_pango_layout_line_get_type ::
IO GType
instance BoxedObject LayoutLine where
boxedType :: LayoutLine -> IO GType
boxedType _ = IO GType
c_pango_layout_line_get_type
instance B.GValue.IsGValue LayoutLine where
toGValue :: LayoutLine -> IO GValue
toGValue o :: LayoutLine
o = do
GType
gtype <- IO GType
c_pango_layout_line_get_type
LayoutLine -> (Ptr LayoutLine -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr LayoutLine
o (GType
-> (GValue -> Ptr LayoutLine -> IO ())
-> Ptr LayoutLine
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr LayoutLine -> IO ()
forall a. GValue -> Ptr a -> IO ()
B.GValue.set_boxed)
fromGValue :: GValue -> IO LayoutLine
fromGValue gv :: GValue
gv = do
Ptr LayoutLine
ptr <- GValue -> IO (Ptr LayoutLine)
forall b. GValue -> IO (Ptr b)
B.GValue.get_boxed GValue
gv :: IO (Ptr LayoutLine)
(ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr LayoutLine -> LayoutLine
LayoutLine Ptr LayoutLine
ptr
newZeroLayoutLine :: MonadIO m => m LayoutLine
newZeroLayoutLine :: m LayoutLine
newZeroLayoutLine = 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
$ Int -> IO (Ptr LayoutLine)
forall a. BoxedObject a => Int -> IO (Ptr a)
callocBoxedBytes 32 IO (Ptr LayoutLine)
-> (Ptr LayoutLine -> IO LayoutLine) -> IO LayoutLine
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= (ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr LayoutLine -> LayoutLine
LayoutLine
instance tag ~ 'AttrSet => Constructible LayoutLine tag where
new :: (ManagedPtr LayoutLine -> LayoutLine)
-> [AttrOp LayoutLine tag] -> m LayoutLine
new _ attrs :: [AttrOp LayoutLine tag]
attrs = do
LayoutLine
o <- m LayoutLine
forall (m :: * -> *). MonadIO m => m LayoutLine
newZeroLayoutLine
LayoutLine -> [AttrOp LayoutLine 'AttrSet] -> m ()
forall o (m :: * -> *).
MonadIO m =>
o -> [AttrOp o 'AttrSet] -> m ()
GI.Attributes.set LayoutLine
o [AttrOp LayoutLine tag]
[AttrOp LayoutLine 'AttrSet]
attrs
LayoutLine -> m LayoutLine
forall (m :: * -> *) a. Monad m => a -> m a
return LayoutLine
o
noLayoutLine :: Maybe LayoutLine
noLayoutLine :: Maybe LayoutLine
noLayoutLine = Maybe LayoutLine
forall a. Maybe a
Nothing
getLayoutLineLayout :: MonadIO m => LayoutLine -> m (Maybe Pango.Layout.Layout)
getLayoutLineLayout :: LayoutLine -> m (Maybe Layout)
getLayoutLineLayout s :: LayoutLine
s = IO (Maybe Layout) -> m (Maybe Layout)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Layout) -> m (Maybe Layout))
-> IO (Maybe Layout) -> m (Maybe Layout)
forall a b. (a -> b) -> a -> b
$ LayoutLine
-> (Ptr LayoutLine -> IO (Maybe Layout)) -> IO (Maybe Layout)
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO (Maybe Layout)) -> IO (Maybe Layout))
-> (Ptr LayoutLine -> IO (Maybe Layout)) -> IO (Maybe Layout)
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr Layout
val <- Ptr (Ptr Layout) -> IO (Ptr Layout)
forall a. Storable a => Ptr a -> IO a
peek (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr (Ptr Layout)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) :: IO (Ptr Pango.Layout.Layout)
Maybe Layout
result <- Ptr Layout -> (Ptr Layout -> IO Layout) -> IO (Maybe Layout)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
SP.convertIfNonNull Ptr Layout
val ((Ptr Layout -> IO Layout) -> IO (Maybe Layout))
-> (Ptr Layout -> IO Layout) -> IO (Maybe Layout)
forall a b. (a -> b) -> a -> b
$ \val' :: Ptr Layout
val' -> do
Layout
val'' <- ((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
val'
Layout -> IO Layout
forall (m :: * -> *) a. Monad m => a -> m a
return Layout
val''
Maybe Layout -> IO (Maybe Layout)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Layout
result
setLayoutLineLayout :: MonadIO m => LayoutLine -> Ptr Pango.Layout.Layout -> m ()
setLayoutLineLayout :: LayoutLine -> Ptr Layout -> m ()
setLayoutLineLayout s :: LayoutLine
s val :: Ptr Layout
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LayoutLine -> (Ptr LayoutLine -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO ()) -> IO ())
-> (Ptr LayoutLine -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr (Ptr Layout) -> Ptr Layout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr (Ptr Layout)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr Layout
val :: Ptr Pango.Layout.Layout)
clearLayoutLineLayout :: MonadIO m => LayoutLine -> m ()
clearLayoutLineLayout :: LayoutLine -> m ()
clearLayoutLineLayout s :: LayoutLine
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LayoutLine -> (Ptr LayoutLine -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO ()) -> IO ())
-> (Ptr LayoutLine -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr (Ptr Layout) -> Ptr Layout -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr (Ptr Layout)
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 0) (Ptr Layout
forall a. Ptr a
FP.nullPtr :: Ptr Pango.Layout.Layout)
#if defined(ENABLE_OVERLOADING)
data LayoutLineLayoutFieldInfo
instance AttrInfo LayoutLineLayoutFieldInfo where
type AttrBaseTypeConstraint LayoutLineLayoutFieldInfo = (~) LayoutLine
type AttrAllowedOps LayoutLineLayoutFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint LayoutLineLayoutFieldInfo = (~) (Ptr Pango.Layout.Layout)
type AttrTransferTypeConstraint LayoutLineLayoutFieldInfo = (~)(Ptr Pango.Layout.Layout)
type AttrTransferType LayoutLineLayoutFieldInfo = (Ptr Pango.Layout.Layout)
type AttrGetType LayoutLineLayoutFieldInfo = Maybe Pango.Layout.Layout
type AttrLabel LayoutLineLayoutFieldInfo = "layout"
type AttrOrigin LayoutLineLayoutFieldInfo = LayoutLine
attrGet = getLayoutLineLayout
attrSet = setLayoutLineLayout
attrConstruct = undefined
attrClear = clearLayoutLineLayout
attrTransfer _ v = do
return v
layoutLine_layout :: AttrLabelProxy "layout"
layoutLine_layout = AttrLabelProxy
#endif
getLayoutLineStartIndex :: MonadIO m => LayoutLine -> m Int32
getLayoutLineStartIndex :: LayoutLine -> m Int32
getLayoutLineStartIndex s :: LayoutLine
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
$ LayoutLine -> (Ptr LayoutLine -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO Int32) -> IO Int32)
-> (Ptr LayoutLine -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setLayoutLineStartIndex :: MonadIO m => LayoutLine -> Int32 -> m ()
setLayoutLineStartIndex :: LayoutLine -> Int32 -> m ()
setLayoutLineStartIndex s :: LayoutLine
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
$ LayoutLine -> (Ptr LayoutLine -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO ()) -> IO ())
-> (Ptr LayoutLine -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 8) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data LayoutLineStartIndexFieldInfo
instance AttrInfo LayoutLineStartIndexFieldInfo where
type AttrBaseTypeConstraint LayoutLineStartIndexFieldInfo = (~) LayoutLine
type AttrAllowedOps LayoutLineStartIndexFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint LayoutLineStartIndexFieldInfo = (~) Int32
type AttrTransferTypeConstraint LayoutLineStartIndexFieldInfo = (~)Int32
type AttrTransferType LayoutLineStartIndexFieldInfo = Int32
type AttrGetType LayoutLineStartIndexFieldInfo = Int32
type AttrLabel LayoutLineStartIndexFieldInfo = "start_index"
type AttrOrigin LayoutLineStartIndexFieldInfo = LayoutLine
attrGet = getLayoutLineStartIndex
attrSet = setLayoutLineStartIndex
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
layoutLine_startIndex :: AttrLabelProxy "startIndex"
layoutLine_startIndex = AttrLabelProxy
#endif
getLayoutLineLength :: MonadIO m => LayoutLine -> m Int32
getLayoutLineLength :: LayoutLine -> m Int32
getLayoutLineLength s :: LayoutLine
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
$ LayoutLine -> (Ptr LayoutLine -> IO Int32) -> IO Int32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO Int32) -> IO Int32)
-> (Ptr LayoutLine -> IO Int32) -> IO Int32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Int32
val <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12) :: IO Int32
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val
setLayoutLineLength :: MonadIO m => LayoutLine -> Int32 -> m ()
setLayoutLineLength :: LayoutLine -> Int32 -> m ()
setLayoutLineLength s :: LayoutLine
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
$ LayoutLine -> (Ptr LayoutLine -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO ()) -> IO ())
-> (Ptr LayoutLine -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr Int32 -> Int32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr Int32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 12) (Int32
val :: Int32)
#if defined(ENABLE_OVERLOADING)
data LayoutLineLengthFieldInfo
instance AttrInfo LayoutLineLengthFieldInfo where
type AttrBaseTypeConstraint LayoutLineLengthFieldInfo = (~) LayoutLine
type AttrAllowedOps LayoutLineLengthFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint LayoutLineLengthFieldInfo = (~) Int32
type AttrTransferTypeConstraint LayoutLineLengthFieldInfo = (~)Int32
type AttrTransferType LayoutLineLengthFieldInfo = Int32
type AttrGetType LayoutLineLengthFieldInfo = Int32
type AttrLabel LayoutLineLengthFieldInfo = "length"
type AttrOrigin LayoutLineLengthFieldInfo = LayoutLine
attrGet = getLayoutLineLength
attrSet = setLayoutLineLength
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
layoutLine_length :: AttrLabelProxy "length"
layoutLine_length = AttrLabelProxy
#endif
getLayoutLineRuns :: MonadIO m => LayoutLine -> m [Pango.GlyphItem.GlyphItem]
getLayoutLineRuns :: LayoutLine -> m [GlyphItem]
getLayoutLineRuns s :: LayoutLine
s = IO [GlyphItem] -> m [GlyphItem]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [GlyphItem] -> m [GlyphItem])
-> IO [GlyphItem] -> m [GlyphItem]
forall a b. (a -> b) -> a -> b
$ LayoutLine -> (Ptr LayoutLine -> IO [GlyphItem]) -> IO [GlyphItem]
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO [GlyphItem]) -> IO [GlyphItem])
-> (Ptr LayoutLine -> IO [GlyphItem]) -> IO [GlyphItem]
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr (GSList (Ptr GlyphItem))
val <- Ptr (Ptr (GSList (Ptr GlyphItem)))
-> IO (Ptr (GSList (Ptr GlyphItem)))
forall a. Storable a => Ptr a -> IO a
peek (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr (Ptr (GSList (Ptr GlyphItem)))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) :: IO (Ptr (GSList (Ptr Pango.GlyphItem.GlyphItem)))
[Ptr GlyphItem]
val' <- Ptr (GSList (Ptr GlyphItem)) -> IO [Ptr GlyphItem]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr GlyphItem))
val
[GlyphItem]
val'' <- (Ptr GlyphItem -> IO GlyphItem)
-> [Ptr GlyphItem] -> IO [GlyphItem]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((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''
setLayoutLineRuns :: MonadIO m => LayoutLine -> Ptr (GSList (Ptr Pango.GlyphItem.GlyphItem)) -> m ()
setLayoutLineRuns :: LayoutLine -> Ptr (GSList (Ptr GlyphItem)) -> m ()
setLayoutLineRuns s :: LayoutLine
s val :: Ptr (GSList (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
$ LayoutLine -> (Ptr LayoutLine -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO ()) -> IO ())
-> (Ptr LayoutLine -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr (Ptr (GSList (Ptr GlyphItem)))
-> Ptr (GSList (Ptr GlyphItem)) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr (Ptr (GSList (Ptr GlyphItem)))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Ptr (GSList (Ptr GlyphItem))
val :: Ptr (GSList (Ptr Pango.GlyphItem.GlyphItem)))
clearLayoutLineRuns :: MonadIO m => LayoutLine -> m ()
clearLayoutLineRuns :: LayoutLine -> m ()
clearLayoutLineRuns s :: LayoutLine
s = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LayoutLine -> (Ptr LayoutLine -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO ()) -> IO ())
-> (Ptr LayoutLine -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr (Ptr (GSList (Ptr GlyphItem)))
-> Ptr (GSList (Ptr GlyphItem)) -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr (Ptr (GSList (Ptr GlyphItem)))
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 16) (Ptr (GSList (Ptr GlyphItem))
forall a. Ptr a
FP.nullPtr :: Ptr (GSList (Ptr Pango.GlyphItem.GlyphItem)))
#if defined(ENABLE_OVERLOADING)
data LayoutLineRunsFieldInfo
instance AttrInfo LayoutLineRunsFieldInfo where
type AttrBaseTypeConstraint LayoutLineRunsFieldInfo = (~) LayoutLine
type AttrAllowedOps LayoutLineRunsFieldInfo = '[ 'AttrSet, 'AttrGet, 'AttrClear]
type AttrSetTypeConstraint LayoutLineRunsFieldInfo = (~) (Ptr (GSList (Ptr Pango.GlyphItem.GlyphItem)))
type AttrTransferTypeConstraint LayoutLineRunsFieldInfo = (~)(Ptr (GSList (Ptr Pango.GlyphItem.GlyphItem)))
type AttrTransferType LayoutLineRunsFieldInfo = (Ptr (GSList (Ptr Pango.GlyphItem.GlyphItem)))
type AttrGetType LayoutLineRunsFieldInfo = [Pango.GlyphItem.GlyphItem]
type AttrLabel LayoutLineRunsFieldInfo = "runs"
type AttrOrigin LayoutLineRunsFieldInfo = LayoutLine
attrGet = getLayoutLineRuns
attrSet = setLayoutLineRuns
attrConstruct = undefined
attrClear = clearLayoutLineRuns
attrTransfer _ v = do
return v
layoutLine_runs :: AttrLabelProxy "runs"
layoutLine_runs = AttrLabelProxy
#endif
getLayoutLineIsParagraphStart :: MonadIO m => LayoutLine -> m Word32
getLayoutLineIsParagraphStart :: LayoutLine -> m Word32
getLayoutLineIsParagraphStart s :: LayoutLine
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ LayoutLine -> (Ptr LayoutLine -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO Word32) -> IO Word32)
-> (Ptr LayoutLine -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setLayoutLineIsParagraphStart :: MonadIO m => LayoutLine -> Word32 -> m ()
setLayoutLineIsParagraphStart :: LayoutLine -> Word32 -> m ()
setLayoutLineIsParagraphStart s :: LayoutLine
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LayoutLine -> (Ptr LayoutLine -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO ()) -> IO ())
-> (Ptr LayoutLine -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 24) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data LayoutLineIsParagraphStartFieldInfo
instance AttrInfo LayoutLineIsParagraphStartFieldInfo where
type AttrBaseTypeConstraint LayoutLineIsParagraphStartFieldInfo = (~) LayoutLine
type AttrAllowedOps LayoutLineIsParagraphStartFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint LayoutLineIsParagraphStartFieldInfo = (~) Word32
type AttrTransferTypeConstraint LayoutLineIsParagraphStartFieldInfo = (~)Word32
type AttrTransferType LayoutLineIsParagraphStartFieldInfo = Word32
type AttrGetType LayoutLineIsParagraphStartFieldInfo = Word32
type AttrLabel LayoutLineIsParagraphStartFieldInfo = "is_paragraph_start"
type AttrOrigin LayoutLineIsParagraphStartFieldInfo = LayoutLine
attrGet = getLayoutLineIsParagraphStart
attrSet = setLayoutLineIsParagraphStart
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
layoutLine_isParagraphStart :: AttrLabelProxy "isParagraphStart"
layoutLine_isParagraphStart = AttrLabelProxy
#endif
getLayoutLineResolvedDir :: MonadIO m => LayoutLine -> m Word32
getLayoutLineResolvedDir :: LayoutLine -> m Word32
getLayoutLineResolvedDir s :: LayoutLine
s = IO Word32 -> m Word32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word32 -> m Word32) -> IO Word32 -> m Word32
forall a b. (a -> b) -> a -> b
$ LayoutLine -> (Ptr LayoutLine -> IO Word32) -> IO Word32
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO Word32) -> IO Word32)
-> (Ptr LayoutLine -> IO Word32) -> IO Word32
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Word32
val <- Ptr Word32 -> IO Word32
forall a. Storable a => Ptr a -> IO a
peek (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28) :: IO Word32
Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val
setLayoutLineResolvedDir :: MonadIO m => LayoutLine -> Word32 -> m ()
setLayoutLineResolvedDir :: LayoutLine -> Word32 -> m ()
setLayoutLineResolvedDir s :: LayoutLine
s val :: Word32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ LayoutLine -> (Ptr LayoutLine -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
withManagedPtr LayoutLine
s ((Ptr LayoutLine -> IO ()) -> IO ())
-> (Ptr LayoutLine -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \ptr :: Ptr LayoutLine
ptr -> do
Ptr Word32 -> Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr LayoutLine
ptr Ptr LayoutLine -> Int -> Ptr Word32
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` 28) (Word32
val :: Word32)
#if defined(ENABLE_OVERLOADING)
data LayoutLineResolvedDirFieldInfo
instance AttrInfo LayoutLineResolvedDirFieldInfo where
type AttrBaseTypeConstraint LayoutLineResolvedDirFieldInfo = (~) LayoutLine
type AttrAllowedOps LayoutLineResolvedDirFieldInfo = '[ 'AttrSet, 'AttrGet]
type AttrSetTypeConstraint LayoutLineResolvedDirFieldInfo = (~) Word32
type AttrTransferTypeConstraint LayoutLineResolvedDirFieldInfo = (~)Word32
type AttrTransferType LayoutLineResolvedDirFieldInfo = Word32
type AttrGetType LayoutLineResolvedDirFieldInfo = Word32
type AttrLabel LayoutLineResolvedDirFieldInfo = "resolved_dir"
type AttrOrigin LayoutLineResolvedDirFieldInfo = LayoutLine
attrGet = getLayoutLineResolvedDir
attrSet = setLayoutLineResolvedDir
attrConstruct = undefined
attrClear = undefined
attrTransfer _ v = do
return v
layoutLine_resolvedDir :: AttrLabelProxy "resolvedDir"
layoutLine_resolvedDir = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList LayoutLine
type instance O.AttributeList LayoutLine = LayoutLineAttributeList
type LayoutLineAttributeList = ('[ '("layout", LayoutLineLayoutFieldInfo), '("startIndex", LayoutLineStartIndexFieldInfo), '("length", LayoutLineLengthFieldInfo), '("runs", LayoutLineRunsFieldInfo), '("isParagraphStart", LayoutLineIsParagraphStartFieldInfo), '("resolvedDir", LayoutLineResolvedDirFieldInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "pango_layout_line_get_extents" pango_layout_line_get_extents ::
Ptr LayoutLine ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutLineGetExtents ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutLine
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutLineGetExtents :: LayoutLine -> m (Rectangle, Rectangle)
layoutLineGetExtents line :: LayoutLine
line = 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 LayoutLine
line' <- LayoutLine -> IO (Ptr LayoutLine)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutLine
line
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 LayoutLine -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_line_get_extents Ptr LayoutLine
line' 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
LayoutLine -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutLine
line
(Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
inkRect', Rectangle
logicalRect')
#if defined(ENABLE_OVERLOADING)
data LayoutLineGetExtentsMethodInfo
instance (signature ~ (m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m) => O.MethodInfo LayoutLineGetExtentsMethodInfo LayoutLine signature where
overloadedMethod = layoutLineGetExtents
#endif
foreign import ccall "pango_layout_line_get_pixel_extents" pango_layout_line_get_pixel_extents ::
Ptr LayoutLine ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutLineGetPixelExtents ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutLine
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutLineGetPixelExtents :: LayoutLine -> m (Rectangle, Rectangle)
layoutLineGetPixelExtents layoutLine :: LayoutLine
layoutLine = 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 LayoutLine
layoutLine' <- LayoutLine -> IO (Ptr LayoutLine)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutLine
layoutLine
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 LayoutLine -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_line_get_pixel_extents Ptr LayoutLine
layoutLine' 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
LayoutLine -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutLine
layoutLine
(Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
inkRect', Rectangle
logicalRect')
#if defined(ENABLE_OVERLOADING)
data LayoutLineGetPixelExtentsMethodInfo
instance (signature ~ (m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m) => O.MethodInfo LayoutLineGetPixelExtentsMethodInfo LayoutLine signature where
overloadedMethod = layoutLineGetPixelExtents
#endif
foreign import ccall "pango_layout_line_get_x_ranges" pango_layout_line_get_x_ranges ::
Ptr LayoutLine ->
Int32 ->
Int32 ->
Ptr (Ptr Int32) ->
Ptr Int32 ->
IO ()
layoutLineGetXRanges ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutLine
-> Int32
-> Int32
-> m ([Int32])
layoutLineGetXRanges :: LayoutLine -> Int32 -> Int32 -> m [Int32]
layoutLineGetXRanges line :: LayoutLine
line startIndex :: Int32
startIndex endIndex :: Int32
endIndex = 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 LayoutLine
line' <- LayoutLine -> IO (Ptr LayoutLine)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutLine
line
Ptr (Ptr Int32)
ranges <- IO (Ptr (Ptr Int32))
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr (Ptr Int32))
Ptr Int32
nRanges <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr LayoutLine
-> Int32 -> Int32 -> Ptr (Ptr Int32) -> Ptr Int32 -> IO ()
pango_layout_line_get_x_ranges Ptr LayoutLine
line' Int32
startIndex Int32
endIndex Ptr (Ptr Int32)
ranges Ptr Int32
nRanges
Int32
nRanges' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nRanges
Ptr Int32
ranges' <- Ptr (Ptr Int32) -> IO (Ptr Int32)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr Int32)
ranges
[Int32]
ranges'' <- (Int32 -> Ptr Int32 -> IO [Int32]
forall a b. (Integral a, Storable b) => a -> Ptr b -> IO [b]
unpackStorableArrayWithLength Int32
nRanges') Ptr Int32
ranges'
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
ranges'
LayoutLine -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutLine
line
Ptr (Ptr Int32) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr Int32)
ranges
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nRanges
[Int32] -> IO [Int32]
forall (m :: * -> *) a. Monad m => a -> m a
return [Int32]
ranges''
#if defined(ENABLE_OVERLOADING)
data LayoutLineGetXRangesMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ([Int32])), MonadIO m) => O.MethodInfo LayoutLineGetXRangesMethodInfo LayoutLine signature where
overloadedMethod = layoutLineGetXRanges
#endif
foreign import ccall "pango_layout_line_index_to_x" pango_layout_line_index_to_x ::
Ptr LayoutLine ->
Int32 ->
CInt ->
Ptr Int32 ->
IO ()
layoutLineIndexToX ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutLine
-> Int32
-> Bool
-> m (Int32)
layoutLineIndexToX :: LayoutLine -> Int32 -> Bool -> m Int32
layoutLineIndexToX line :: LayoutLine
line index_ :: Int32
index_ trailing :: Bool
trailing = 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 LayoutLine
line' <- LayoutLine -> IO (Ptr LayoutLine)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutLine
line
let trailing' :: CInt
trailing' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
trailing
Ptr Int32
xPos <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr LayoutLine -> Int32 -> CInt -> Ptr Int32 -> IO ()
pango_layout_line_index_to_x Ptr LayoutLine
line' Int32
index_ CInt
trailing' Ptr Int32
xPos
Int32
xPos' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
xPos
LayoutLine -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutLine
line
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
xPos
Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
xPos'
#if defined(ENABLE_OVERLOADING)
data LayoutLineIndexToXMethodInfo
instance (signature ~ (Int32 -> Bool -> m (Int32)), MonadIO m) => O.MethodInfo LayoutLineIndexToXMethodInfo LayoutLine signature where
overloadedMethod = layoutLineIndexToX
#endif
foreign import ccall "pango_layout_line_ref" pango_layout_line_ref ::
Ptr LayoutLine ->
IO (Ptr LayoutLine)
layoutLineRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutLine
-> m LayoutLine
layoutLineRef :: LayoutLine -> m LayoutLine
layoutLineRef line :: LayoutLine
line = 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 LayoutLine
line' <- LayoutLine -> IO (Ptr LayoutLine)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutLine
line
Ptr LayoutLine
result <- Ptr LayoutLine -> IO (Ptr LayoutLine)
pango_layout_line_ref Ptr LayoutLine
line'
Text -> Ptr LayoutLine -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "layoutLineRef" Ptr LayoutLine
result
LayoutLine
result' <- ((ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr LayoutLine -> LayoutLine
LayoutLine) Ptr LayoutLine
result
LayoutLine -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutLine
line
LayoutLine -> IO LayoutLine
forall (m :: * -> *) a. Monad m => a -> m a
return LayoutLine
result'
#if defined(ENABLE_OVERLOADING)
data LayoutLineRefMethodInfo
instance (signature ~ (m LayoutLine), MonadIO m) => O.MethodInfo LayoutLineRefMethodInfo LayoutLine signature where
overloadedMethod = layoutLineRef
#endif
foreign import ccall "pango_layout_line_unref" pango_layout_line_unref ::
Ptr LayoutLine ->
IO ()
layoutLineUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutLine
-> m ()
layoutLineUnref :: LayoutLine -> m ()
layoutLineUnref line :: LayoutLine
line = 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 LayoutLine
line' <- LayoutLine -> IO (Ptr LayoutLine)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutLine
line
Ptr LayoutLine -> IO ()
pango_layout_line_unref Ptr LayoutLine
line'
LayoutLine -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutLine
line
() -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data LayoutLineUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.MethodInfo LayoutLineUnrefMethodInfo LayoutLine signature where
overloadedMethod = layoutLineUnref
#endif
foreign import ccall "pango_layout_line_x_to_index" pango_layout_line_x_to_index ::
Ptr LayoutLine ->
Int32 ->
Ptr Int32 ->
Ptr Int32 ->
IO CInt
layoutLineXToIndex ::
(B.CallStack.HasCallStack, MonadIO m) =>
LayoutLine
-> Int32
-> m ((Bool, Int32, Int32))
layoutLineXToIndex :: LayoutLine -> Int32 -> m (Bool, Int32, Int32)
layoutLineXToIndex line :: LayoutLine
line xPos :: Int32
xPos = IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32))
-> IO (Bool, Int32, Int32) -> m (Bool, Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
Ptr LayoutLine
line' <- LayoutLine -> IO (Ptr LayoutLine)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutLine
line
Ptr Int32
index_ <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
Ptr Int32
trailing <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
CInt
result <- Ptr LayoutLine -> Int32 -> Ptr Int32 -> Ptr Int32 -> IO CInt
pango_layout_line_x_to_index Ptr LayoutLine
line' Int32
xPos Ptr Int32
index_ Ptr Int32
trailing
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
Int32
index_' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
index_
Int32
trailing' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
trailing
LayoutLine -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutLine
line
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
index_
Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
trailing
(Bool, Int32, Int32) -> IO (Bool, Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Int32
index_', Int32
trailing')
#if defined(ENABLE_OVERLOADING)
data LayoutLineXToIndexMethodInfo
instance (signature ~ (Int32 -> m ((Bool, Int32, Int32))), MonadIO m) => O.MethodInfo LayoutLineXToIndexMethodInfo LayoutLine signature where
overloadedMethod = layoutLineXToIndex
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolveLayoutLineMethod (t :: Symbol) (o :: *) :: * where
ResolveLayoutLineMethod "indexToX" o = LayoutLineIndexToXMethodInfo
ResolveLayoutLineMethod "ref" o = LayoutLineRefMethodInfo
ResolveLayoutLineMethod "unref" o = LayoutLineUnrefMethodInfo
ResolveLayoutLineMethod "xToIndex" o = LayoutLineXToIndexMethodInfo
ResolveLayoutLineMethod "getExtents" o = LayoutLineGetExtentsMethodInfo
ResolveLayoutLineMethod "getPixelExtents" o = LayoutLineGetPixelExtentsMethodInfo
ResolveLayoutLineMethod "getXRanges" o = LayoutLineGetXRangesMethodInfo
ResolveLayoutLineMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveLayoutLineMethod t LayoutLine, O.MethodInfo info LayoutLine p) => OL.IsLabel t (LayoutLine -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#endif