{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- The t'GI.Pango.Structs.LayoutLine.LayoutLine' structure represents one of the lines resulting
-- from laying out a paragraph via t'GI.Pango.Objects.Layout.Layout'. t'GI.Pango.Structs.LayoutLine.LayoutLine'
-- structures are obtained by calling 'GI.Pango.Objects.Layout.layoutGetLine' and
-- are only valid until the text, attributes, or settings of the
-- parent t'GI.Pango.Objects.Layout.Layout' are modified.
-- 
-- Routines for rendering PangoLayout objects are provided in
-- code specific to each rendering system.

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

module GI.Pango.Structs.LayoutLine
    ( 

-- * Exported types
    LayoutLine(..)                          ,
    newZeroLayoutLine                       ,


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

#if defined(ENABLE_OVERLOADING)
    ResolveLayoutLineMethod                 ,
#endif


-- ** getExtents #method:getExtents#

#if defined(ENABLE_OVERLOADING)
    LayoutLineGetExtentsMethodInfo          ,
#endif
    layoutLineGetExtents                    ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    LayoutLineGetHeightMethodInfo           ,
#endif
    layoutLineGetHeight                     ,


-- ** getPixelExtents #method:getPixelExtents#

#if defined(ENABLE_OVERLOADING)
    LayoutLineGetPixelExtentsMethodInfo     ,
#endif
    layoutLineGetPixelExtents               ,


-- ** getXRanges #method:getXRanges#

#if defined(ENABLE_OVERLOADING)
    LayoutLineGetXRangesMethodInfo          ,
#endif
    layoutLineGetXRanges                    ,


-- ** indexToX #method:indexToX#

#if defined(ENABLE_OVERLOADING)
    LayoutLineIndexToXMethodInfo            ,
#endif
    layoutLineIndexToX                      ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    LayoutLineRefMethodInfo                 ,
#endif
    layoutLineRef                           ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    LayoutLineUnrefMethodInfo               ,
#endif
    layoutLineUnref                         ,


-- ** xToIndex #method:xToIndex#

#if defined(ENABLE_OVERLOADING)
    LayoutLineXToIndexMethodInfo            ,
#endif
    layoutLineXToIndex                      ,




 -- * Properties
-- ** isParagraphStart #attr:isParagraphStart#
-- | @/TRUE/@ if this is the first line of the paragraph

    getLayoutLineIsParagraphStart           ,
#if defined(ENABLE_OVERLOADING)
    layoutLine_isParagraphStart             ,
#endif
    setLayoutLineIsParagraphStart           ,


-- ** layout #attr:layout#
-- | the layout this line belongs to, might be 'P.Nothing'

    clearLayoutLineLayout                   ,
    getLayoutLineLayout                     ,
#if defined(ENABLE_OVERLOADING)
    layoutLine_layout                       ,
#endif
    setLayoutLineLayout                     ,


-- ** length #attr:length#
-- | length of line in bytes

    getLayoutLineLength                     ,
#if defined(ENABLE_OVERLOADING)
    layoutLine_length                       ,
#endif
    setLayoutLineLength                     ,


-- ** resolvedDir #attr:resolvedDir#
-- | @/Resolved/@ PangoDirection of line

    getLayoutLineResolvedDir                ,
#if defined(ENABLE_OVERLOADING)
    layoutLine_resolvedDir                  ,
#endif
    setLayoutLineResolvedDir                ,


-- ** runs #attr:runs#
-- | list of runs in the
--        line, from left to right

    clearLayoutLineRuns                     ,
    getLayoutLineRuns                       ,
#if defined(ENABLE_OVERLOADING)
    layoutLine_runs                         ,
#endif
    setLayoutLineRuns                       ,


-- ** startIndex #attr:startIndex#
-- | start of line as byte index into layout->text

    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.BasicTypes as B.Types
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 Control.Monad.IO.Class as MIO
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

-- | Memory-managed wrapper type.
newtype LayoutLine = LayoutLine (SP.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)

instance SP.ManagedPtrNewtype LayoutLine where
    toManagedPtr :: LayoutLine -> ManagedPtr LayoutLine
toManagedPtr (LayoutLine ManagedPtr LayoutLine
p) = ManagedPtr LayoutLine
p

foreign import ccall "pango_layout_line_get_type" c_pango_layout_line_get_type :: 
    IO GType

type instance O.ParentTypes LayoutLine = '[]
instance O.HasParentTypes LayoutLine

instance B.Types.TypedObject LayoutLine where
    glibType :: IO GType
glibType = IO GType
c_pango_layout_line_get_type

instance B.Types.GBoxed LayoutLine

-- | Convert 'LayoutLine' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue LayoutLine where
    toGValue :: LayoutLine -> IO GValue
toGValue 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 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, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
B.ManagedPtr.newBoxed ManagedPtr LayoutLine -> LayoutLine
LayoutLine Ptr LayoutLine
ptr
        
    

-- | Construct a `LayoutLine` struct initialized to zero.
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. GBoxed a => Int -> IO (Ptr a)
callocBoxedBytes Int
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, GBoxed 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 ManagedPtr LayoutLine -> LayoutLine
_ [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


-- | Get the value of the “@layout@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' layoutLine #layout
-- @
getLayoutLineLayout :: MonadIO m => LayoutLine -> m (Maybe Pango.Layout.Layout)
getLayoutLineLayout :: LayoutLine -> m (Maybe Layout)
getLayoutLineLayout 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 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` Int
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
$ \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

-- | Set the value of the “@layout@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' layoutLine [ #layout 'Data.GI.Base.Attributes.:=' value ]
-- @
setLayoutLineLayout :: MonadIO m => LayoutLine -> Ptr Pango.Layout.Layout -> m ()
setLayoutLineLayout :: LayoutLine -> Ptr Layout -> m ()
setLayoutLineLayout LayoutLine
s 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 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` Int
0) (Ptr Layout
val :: Ptr Pango.Layout.Layout)

-- | Set the value of the “@layout@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #layout
-- @
clearLayoutLineLayout :: MonadIO m => LayoutLine -> m ()
clearLayoutLineLayout :: LayoutLine -> m ()
clearLayoutLineLayout 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 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` Int
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


-- | Get the value of the “@start_index@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' layoutLine #startIndex
-- @
getLayoutLineStartIndex :: MonadIO m => LayoutLine -> m Int32
getLayoutLineStartIndex :: LayoutLine -> m Int32
getLayoutLineStartIndex 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 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` Int
8) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@start_index@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' layoutLine [ #startIndex 'Data.GI.Base.Attributes.:=' value ]
-- @
setLayoutLineStartIndex :: MonadIO m => LayoutLine -> Int32 -> m ()
setLayoutLineStartIndex :: LayoutLine -> Int32 -> m ()
setLayoutLineStartIndex LayoutLine
s 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 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` Int
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


-- | Get the value of the “@length@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' layoutLine #length
-- @
getLayoutLineLength :: MonadIO m => LayoutLine -> m Int32
getLayoutLineLength :: LayoutLine -> m Int32
getLayoutLineLength 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 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` Int
12) :: IO Int32
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
val

-- | Set the value of the “@length@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' layoutLine [ #length 'Data.GI.Base.Attributes.:=' value ]
-- @
setLayoutLineLength :: MonadIO m => LayoutLine -> Int32 -> m ()
setLayoutLineLength :: LayoutLine -> Int32 -> m ()
setLayoutLineLength LayoutLine
s 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 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` Int
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


-- | Get the value of the “@runs@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' layoutLine #runs
-- @
getLayoutLineRuns :: MonadIO m => LayoutLine -> m [Pango.GlyphItem.GlyphItem]
getLayoutLineRuns :: LayoutLine -> m [GlyphItem]
getLayoutLineRuns 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 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` Int
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, GBoxed 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''

-- | Set the value of the “@runs@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' layoutLine [ #runs 'Data.GI.Base.Attributes.:=' value ]
-- @
setLayoutLineRuns :: MonadIO m => LayoutLine -> Ptr (GSList (Ptr Pango.GlyphItem.GlyphItem)) -> m ()
setLayoutLineRuns :: LayoutLine -> Ptr (GSList (Ptr GlyphItem)) -> m ()
setLayoutLineRuns LayoutLine
s 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 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` Int
16) (Ptr (GSList (Ptr GlyphItem))
val :: Ptr (GSList (Ptr Pango.GlyphItem.GlyphItem)))

-- | Set the value of the “@runs@” field to `Nothing`.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.clear' #runs
-- @
clearLayoutLineRuns :: MonadIO m => LayoutLine -> m ()
clearLayoutLineRuns :: LayoutLine -> m ()
clearLayoutLineRuns 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 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` Int
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


-- | Get the value of the “@is_paragraph_start@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' layoutLine #isParagraphStart
-- @
getLayoutLineIsParagraphStart :: MonadIO m => LayoutLine -> m Word32
getLayoutLineIsParagraphStart :: LayoutLine -> m Word32
getLayoutLineIsParagraphStart 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 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` Int
24) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@is_paragraph_start@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' layoutLine [ #isParagraphStart 'Data.GI.Base.Attributes.:=' value ]
-- @
setLayoutLineIsParagraphStart :: MonadIO m => LayoutLine -> Word32 -> m ()
setLayoutLineIsParagraphStart :: LayoutLine -> Word32 -> m ()
setLayoutLineIsParagraphStart LayoutLine
s 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 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` Int
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


-- | Get the value of the “@resolved_dir@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' layoutLine #resolvedDir
-- @
getLayoutLineResolvedDir :: MonadIO m => LayoutLine -> m Word32
getLayoutLineResolvedDir :: LayoutLine -> m Word32
getLayoutLineResolvedDir 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 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` Int
28) :: IO Word32
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
val

-- | Set the value of the “@resolved_dir@” field.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' layoutLine [ #resolvedDir 'Data.GI.Base.Attributes.:=' value ]
-- @
setLayoutLineResolvedDir :: MonadIO m => LayoutLine -> Word32 -> m ()
setLayoutLineResolvedDir :: LayoutLine -> Word32 -> m ()
setLayoutLineResolvedDir LayoutLine
s 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 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` Int
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

-- method LayoutLine::get_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "line"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "LayoutLine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoLayoutLine" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ink_rect"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "rectangle used to store the extents of\n           the glyph string as drawn, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "logical_rect"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "rectangle used to store the logical\n               extents of the glyph string, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_line_get_extents" pango_layout_line_get_extents :: 
    Ptr LayoutLine ->                       -- line : TInterface (Name {namespace = "Pango", name = "LayoutLine"})
    Ptr Pango.Rectangle.Rectangle ->        -- ink_rect : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    Ptr Pango.Rectangle.Rectangle ->        -- logical_rect : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    IO ()

-- | Computes the logical and ink extents of a layout line. See
-- 'GI.Pango.Objects.Font.fontGetGlyphExtents' for details about the interpretation
-- of the rectangles.
layoutLineGetExtents ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    LayoutLine
    -- ^ /@line@/: a t'GI.Pango.Structs.LayoutLine.LayoutLine'
    -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutLineGetExtents :: LayoutLine -> m (Rectangle, Rectangle)
layoutLineGetExtents 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)
SP.callocBytes Int
16 :: IO (Ptr Pango.Rectangle.Rectangle)
    Ptr Rectangle
logicalRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
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, BoxedPtr 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, BoxedPtr 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

-- method LayoutLine::get_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "line"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "LayoutLine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoLayoutLine" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the line height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_line_get_height" pango_layout_line_get_height :: 
    Ptr LayoutLine ->                       -- line : TInterface (Name {namespace = "Pango", name = "LayoutLine"})
    Ptr Int32 ->                            -- height : TBasicType TInt
    IO ()

-- | Computes the height of the line, ie the distance between
-- this and the previous lines baseline.
-- 
-- /Since: 1.44/
layoutLineGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    LayoutLine
    -- ^ /@line@/: a t'GI.Pango.Structs.LayoutLine.LayoutLine'
    -> m (Int32)
layoutLineGetHeight :: LayoutLine -> m Int32
layoutLineGetHeight LayoutLine
line = 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 Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr LayoutLine -> Ptr Int32 -> IO ()
pango_layout_line_get_height Ptr LayoutLine
line' Ptr Int32
height
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    LayoutLine -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutLine
line
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
height'

#if defined(ENABLE_OVERLOADING)
data LayoutLineGetHeightMethodInfo
instance (signature ~ (m (Int32)), MonadIO m) => O.MethodInfo LayoutLineGetHeightMethodInfo LayoutLine signature where
    overloadedMethod = layoutLineGetHeight

#endif

-- method LayoutLine::get_pixel_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout_line"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "LayoutLine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoLayoutLine" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ink_rect"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "rectangle used to store the extents of\n                  the glyph string as drawn, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "logical_rect"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "rectangle used to store the logical\n                      extents of the glyph string, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_line_get_pixel_extents" pango_layout_line_get_pixel_extents :: 
    Ptr LayoutLine ->                       -- layout_line : TInterface (Name {namespace = "Pango", name = "LayoutLine"})
    Ptr Pango.Rectangle.Rectangle ->        -- ink_rect : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    Ptr Pango.Rectangle.Rectangle ->        -- logical_rect : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    IO ()

-- | Computes the logical and ink extents of /@layoutLine@/ in device units.
-- This function just calls 'GI.Pango.Structs.LayoutLine.layoutLineGetExtents' followed by
-- two 'GI.Pango.Functions.extentsToPixels' calls, rounding /@inkRect@/ and /@logicalRect@/
-- such that the rounded rectangles fully contain the unrounded one (that is,
-- passes them as first argument to 'GI.Pango.Functions.extentsToPixels').
layoutLineGetPixelExtents ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    LayoutLine
    -- ^ /@layoutLine@/: a t'GI.Pango.Structs.LayoutLine.LayoutLine'
    -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutLineGetPixelExtents :: LayoutLine -> m (Rectangle, Rectangle)
layoutLineGetPixelExtents 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)
SP.callocBytes Int
16 :: IO (Ptr Pango.Rectangle.Rectangle)
    Ptr Rectangle
logicalRect <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
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, BoxedPtr 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, BoxedPtr 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

-- method LayoutLine::get_x_ranges
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "line"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "LayoutLine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoLayoutLine" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "start_index"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Start byte index of the logical range. If this value\n              is less than the start index for the line, then\n              the first range will extend all the way to the leading\n              edge of the layout. Otherwise it will start at the\n              leading edge of the first character."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "end_index"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Ending byte index of the logical range. If this value\n              is greater than the end index for the line, then\n              the last range will extend all the way to the trailing\n              edge of the layout. Otherwise, it will end at the\n              trailing edge of the last character."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ranges"
--           , argType = TCArray False (-1) 4 (TBasicType TInt)
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "\n              location to store a pointer to an array of ranges.\n              The array will be of length <literal>2*n_ranges</literal>,\n              with each range starting at <literal>(*ranges)[2*n]</literal>\n              and of width <literal>(*ranges)[2*n + 1] - (*ranges)[2*n]</literal>.\n              This array must be freed with g_free(). The coordinates are relative\n              to the layout and are in Pango units."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "n_ranges"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "The number of ranges stored in @ranges."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_ranges"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "The number of ranges stored in @ranges."
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_line_get_x_ranges" pango_layout_line_get_x_ranges :: 
    Ptr LayoutLine ->                       -- line : TInterface (Name {namespace = "Pango", name = "LayoutLine"})
    Int32 ->                                -- start_index : TBasicType TInt
    Int32 ->                                -- end_index : TBasicType TInt
    Ptr (Ptr Int32) ->                      -- ranges : TCArray False (-1) 4 (TBasicType TInt)
    Ptr Int32 ->                            -- n_ranges : TBasicType TInt
    IO ()

-- | Gets a list of visual ranges corresponding to a given logical range.
-- This list is not necessarily minimal - there may be consecutive
-- ranges which are adjacent. The ranges will be sorted from left to
-- right. The ranges are with respect to the left edge of the entire
-- layout, not with respect to the line.
layoutLineGetXRanges ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    LayoutLine
    -- ^ /@line@/: a t'GI.Pango.Structs.LayoutLine.LayoutLine'
    -> Int32
    -- ^ /@startIndex@/: Start byte index of the logical range. If this value
    --               is less than the start index for the line, then
    --               the first range will extend all the way to the leading
    --               edge of the layout. Otherwise it will start at the
    --               leading edge of the first character.
    -> Int32
    -- ^ /@endIndex@/: Ending byte index of the logical range. If this value
    --               is greater than the end index for the line, then
    --               the last range will extend all the way to the trailing
    --               edge of the layout. Otherwise, it will end at the
    --               trailing edge of the last character.
    -> m ([Int32])
layoutLineGetXRanges :: LayoutLine -> Int32 -> Int32 -> m [Int32]
layoutLineGetXRanges LayoutLine
line Int32
startIndex 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)
callocMem :: 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

-- method LayoutLine::index_to_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "line"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "LayoutLine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoLayoutLine" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "byte offset of a grapheme within the layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "trailing"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "an integer indicating the edge of the grapheme to retrieve\n           the position of. If > 0, the trailing edge of the grapheme,\n           if 0, the leading of the grapheme."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_pos"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "location to store the x_offset (in Pango unit)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_line_index_to_x" pango_layout_line_index_to_x :: 
    Ptr LayoutLine ->                       -- line : TInterface (Name {namespace = "Pango", name = "LayoutLine"})
    Int32 ->                                -- index_ : TBasicType TInt
    CInt ->                                 -- trailing : TBasicType TBoolean
    Ptr Int32 ->                            -- x_pos : TBasicType TInt
    IO ()

-- | Converts an index within a line to a X position.
layoutLineIndexToX ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    LayoutLine
    -- ^ /@line@/: a t'GI.Pango.Structs.LayoutLine.LayoutLine'
    -> Int32
    -- ^ /@index_@/: byte offset of a grapheme within the layout
    -> Bool
    -- ^ /@trailing@/: an integer indicating the edge of the grapheme to retrieve
    --            the position of. If > 0, the trailing edge of the grapheme,
    --            if 0, the leading of the grapheme.
    -> m (Int32)
layoutLineIndexToX :: LayoutLine -> Int32 -> Bool -> m Int32
layoutLineIndexToX LayoutLine
line Int32
index_ 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

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

foreign import ccall "pango_layout_line_ref" pango_layout_line_ref :: 
    Ptr LayoutLine ->                       -- line : TInterface (Name {namespace = "Pango", name = "LayoutLine"})
    IO (Ptr LayoutLine)

-- | Increase the reference count of a t'GI.Pango.Structs.LayoutLine.LayoutLine' by one.
-- 
-- /Since: 1.10/
layoutLineRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    LayoutLine
    -- ^ /@line@/: a t'GI.Pango.Structs.LayoutLine.LayoutLine', may be 'P.Nothing'
    -> m LayoutLine
    -- ^ __Returns:__ the line passed in.
layoutLineRef :: LayoutLine -> m LayoutLine
layoutLineRef 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 Text
"layoutLineRef" Ptr LayoutLine
result
    LayoutLine
result' <- ((ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, GBoxed 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

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

foreign import ccall "pango_layout_line_unref" pango_layout_line_unref :: 
    Ptr LayoutLine ->                       -- line : TInterface (Name {namespace = "Pango", name = "LayoutLine"})
    IO ()

-- | Decrease the reference count of a t'GI.Pango.Structs.LayoutLine.LayoutLine' by one.
-- If the result is zero, the line and all associated memory
-- will be freed.
layoutLineUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    LayoutLine
    -- ^ /@line@/: a t'GI.Pango.Structs.LayoutLine.LayoutLine'
    -> m ()
layoutLineUnref :: LayoutLine -> m ()
layoutLineUnref 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

-- method LayoutLine::x_to_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "line"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "LayoutLine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #PangoLayoutLine" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x_pos"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the X offset (in Pango units)\n            from the left edge of the line."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "index_"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store calculated byte index for\n                  the grapheme in which the user clicked."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "trailing"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store an integer indicating where\n                  in the grapheme the user clicked. It will either\n                  be zero, or the number of characters in the\n                  grapheme. 0 represents the leading edge of the grapheme."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_line_x_to_index" pango_layout_line_x_to_index :: 
    Ptr LayoutLine ->                       -- line : TInterface (Name {namespace = "Pango", name = "LayoutLine"})
    Int32 ->                                -- x_pos : TBasicType TInt
    Ptr Int32 ->                            -- index_ : TBasicType TInt
    Ptr Int32 ->                            -- trailing : TBasicType TInt
    IO CInt

-- | Converts from x offset to the byte index of the corresponding
-- character within the text of the layout. If /@xPos@/ is outside the line,
-- /@index_@/ and /@trailing@/ will point to the very first or very last position
-- in the line. This determination is based on the resolved direction
-- of the paragraph; for example, if the resolved direction is
-- right-to-left, then an X position to the right of the line (after it)
-- results in 0 being stored in /@index_@/ and /@trailing@/. An X position to the
-- left of the line results in /@index_@/ pointing to the (logical) last
-- grapheme in the line and /@trailing@/ being set to the number of characters
-- in that grapheme. The reverse is true for a left-to-right line.
layoutLineXToIndex ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    LayoutLine
    -- ^ /@line@/: a t'GI.Pango.Structs.LayoutLine.LayoutLine'
    -> Int32
    -- ^ /@xPos@/: the X offset (in Pango units)
    --             from the left edge of the line.
    -> m ((Bool, Int32, Int32))
    -- ^ __Returns:__ 'P.False' if /@xPos@/ was outside the line, 'P.True' if inside
layoutLineXToIndex :: LayoutLine -> Int32 -> m (Bool, Int32, Int32)
layoutLineXToIndex LayoutLine
line 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
/= CInt
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 "getHeight" o = LayoutLineGetHeightMethodInfo
    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