{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @PangoLayout@ structure represents an entire paragraph of text.
-- 
-- While complete access to the layout capabilities of Pango is provided
-- using the detailed interfaces for itemization and shaping, using
-- that functionality directly involves writing a fairly large amount
-- of code. @PangoLayout@ provides a high-level driver for formatting
-- entire paragraphs of text at once. This includes paragraph-level
-- functionality such as line breaking, justification, alignment and
-- ellipsization.
-- 
-- A @PangoLayout@ is initialized with a @PangoContext@, UTF-8 string
-- and set of attributes for that string. Once that is done, the set of
-- formatted lines can be extracted from the object, the layout can be
-- rendered, and conversion between logical character positions within
-- the layout\'s text, and the physical position of the resulting glyphs
-- can be made.
-- 
-- There are a number of parameters to adjust the formatting of a
-- @PangoLayout@. The following image shows adjustable parameters
-- (on the left) and font metrics (on the right):
-- 
-- \<picture>
--   \<source srcset=\"layout-dark.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img alt=\"Pango Layout Parameters\" src=\"layout-light.png\">
-- \<\/picture>
-- 
-- The following images demonstrate the effect of alignment and
-- justification on the layout of text:
-- 
-- | | |
-- | --- | --- |
-- | <<http://developer.gnome.org/pango/stable/align-left.png align=left>> | <<http://developer.gnome.org/pango/stable/align-left-justify.png align=left, justify>> |
-- | <<http://developer.gnome.org/pango/stable/align-center.png align=center>> | <<http://developer.gnome.org/pango/stable/align-center-justify.png align=center, justify>> |
-- | <<http://developer.gnome.org/pango/stable/align-right.png align=right>> | <<http://developer.gnome.org/pango/stable/align-right-justify.png align=right, justify>> |
-- 
-- 
-- It is possible, as well, to ignore the 2-D setup,
-- and simply treat the results of a @PangoLayout@ as a list of lines.

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

module GI.Pango.Objects.Layout
    ( 
#if defined(ENABLE_OVERLOADING)
    LayoutSetMarkupWithAccelMethodInfo      ,
#endif

-- * Exported types
    Layout(..)                              ,
    IsLayout                                ,
    toLayout                                ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [contextChanged]("GI.Pango.Objects.Layout#g:method:contextChanged"), [copy]("GI.Pango.Objects.Layout#g:method:copy"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [indexToLineX]("GI.Pango.Objects.Layout#g:method:indexToLineX"), [indexToPos]("GI.Pango.Objects.Layout#g:method:indexToPos"), [isEllipsized]("GI.Pango.Objects.Layout#g:method:isEllipsized"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isWrapped]("GI.Pango.Objects.Layout#g:method:isWrapped"), [moveCursorVisually]("GI.Pango.Objects.Layout#g:method:moveCursorVisually"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [serialize]("GI.Pango.Objects.Layout#g:method:serialize"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure"), [writeToFile]("GI.Pango.Objects.Layout#g:method:writeToFile"), [xyToIndex]("GI.Pango.Objects.Layout#g:method:xyToIndex").
-- 
-- ==== Getters
-- [getAlignment]("GI.Pango.Objects.Layout#g:method:getAlignment"), [getAttributes]("GI.Pango.Objects.Layout#g:method:getAttributes"), [getAutoDir]("GI.Pango.Objects.Layout#g:method:getAutoDir"), [getBaseline]("GI.Pango.Objects.Layout#g:method:getBaseline"), [getCaretPos]("GI.Pango.Objects.Layout#g:method:getCaretPos"), [getCharacterCount]("GI.Pango.Objects.Layout#g:method:getCharacterCount"), [getContext]("GI.Pango.Objects.Layout#g:method:getContext"), [getCursorPos]("GI.Pango.Objects.Layout#g:method:getCursorPos"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDirection]("GI.Pango.Objects.Layout#g:method:getDirection"), [getEllipsize]("GI.Pango.Objects.Layout#g:method:getEllipsize"), [getExtents]("GI.Pango.Objects.Layout#g:method:getExtents"), [getFontDescription]("GI.Pango.Objects.Layout#g:method:getFontDescription"), [getHeight]("GI.Pango.Objects.Layout#g:method:getHeight"), [getIndent]("GI.Pango.Objects.Layout#g:method:getIndent"), [getIter]("GI.Pango.Objects.Layout#g:method:getIter"), [getJustify]("GI.Pango.Objects.Layout#g:method:getJustify"), [getJustifyLastLine]("GI.Pango.Objects.Layout#g:method:getJustifyLastLine"), [getLine]("GI.Pango.Objects.Layout#g:method:getLine"), [getLineCount]("GI.Pango.Objects.Layout#g:method:getLineCount"), [getLineReadonly]("GI.Pango.Objects.Layout#g:method:getLineReadonly"), [getLineSpacing]("GI.Pango.Objects.Layout#g:method:getLineSpacing"), [getLines]("GI.Pango.Objects.Layout#g:method:getLines"), [getLinesReadonly]("GI.Pango.Objects.Layout#g:method:getLinesReadonly"), [getLogAttrs]("GI.Pango.Objects.Layout#g:method:getLogAttrs"), [getLogAttrsReadonly]("GI.Pango.Objects.Layout#g:method:getLogAttrsReadonly"), [getPixelExtents]("GI.Pango.Objects.Layout#g:method:getPixelExtents"), [getPixelSize]("GI.Pango.Objects.Layout#g:method:getPixelSize"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSerial]("GI.Pango.Objects.Layout#g:method:getSerial"), [getSingleParagraphMode]("GI.Pango.Objects.Layout#g:method:getSingleParagraphMode"), [getSize]("GI.Pango.Objects.Layout#g:method:getSize"), [getSpacing]("GI.Pango.Objects.Layout#g:method:getSpacing"), [getTabs]("GI.Pango.Objects.Layout#g:method:getTabs"), [getText]("GI.Pango.Objects.Layout#g:method:getText"), [getUnknownGlyphsCount]("GI.Pango.Objects.Layout#g:method:getUnknownGlyphsCount"), [getWidth]("GI.Pango.Objects.Layout#g:method:getWidth"), [getWrap]("GI.Pango.Objects.Layout#g:method:getWrap").
-- 
-- ==== Setters
-- [setAlignment]("GI.Pango.Objects.Layout#g:method:setAlignment"), [setAttributes]("GI.Pango.Objects.Layout#g:method:setAttributes"), [setAutoDir]("GI.Pango.Objects.Layout#g:method:setAutoDir"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setEllipsize]("GI.Pango.Objects.Layout#g:method:setEllipsize"), [setFontDescription]("GI.Pango.Objects.Layout#g:method:setFontDescription"), [setHeight]("GI.Pango.Objects.Layout#g:method:setHeight"), [setIndent]("GI.Pango.Objects.Layout#g:method:setIndent"), [setJustify]("GI.Pango.Objects.Layout#g:method:setJustify"), [setJustifyLastLine]("GI.Pango.Objects.Layout#g:method:setJustifyLastLine"), [setLineSpacing]("GI.Pango.Objects.Layout#g:method:setLineSpacing"), [setMarkup]("GI.Pango.Objects.Layout#g:method:setMarkup"), [setMarkupWithAccel]("GI.Pango.Objects.Layout#g:method:setMarkupWithAccel"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setSingleParagraphMode]("GI.Pango.Objects.Layout#g:method:setSingleParagraphMode"), [setSpacing]("GI.Pango.Objects.Layout#g:method:setSpacing"), [setTabs]("GI.Pango.Objects.Layout#g:method:setTabs"), [setText]("GI.Pango.Objects.Layout#g:method:setText"), [setWidth]("GI.Pango.Objects.Layout#g:method:setWidth"), [setWrap]("GI.Pango.Objects.Layout#g:method:setWrap").

#if defined(ENABLE_OVERLOADING)
    ResolveLayoutMethod                     ,
#endif

-- ** contextChanged #method:contextChanged#

#if defined(ENABLE_OVERLOADING)
    LayoutContextChangedMethodInfo          ,
#endif
    layoutContextChanged                    ,


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    LayoutCopyMethodInfo                    ,
#endif
    layoutCopy                              ,


-- ** deserialize #method:deserialize#

    layoutDeserialize                       ,


-- ** getAlignment #method:getAlignment#

#if defined(ENABLE_OVERLOADING)
    LayoutGetAlignmentMethodInfo            ,
#endif
    layoutGetAlignment                      ,


-- ** getAttributes #method:getAttributes#

#if defined(ENABLE_OVERLOADING)
    LayoutGetAttributesMethodInfo           ,
#endif
    layoutGetAttributes                     ,


-- ** getAutoDir #method:getAutoDir#

#if defined(ENABLE_OVERLOADING)
    LayoutGetAutoDirMethodInfo              ,
#endif
    layoutGetAutoDir                        ,


-- ** getBaseline #method:getBaseline#

#if defined(ENABLE_OVERLOADING)
    LayoutGetBaselineMethodInfo             ,
#endif
    layoutGetBaseline                       ,


-- ** getCaretPos #method:getCaretPos#

#if defined(ENABLE_OVERLOADING)
    LayoutGetCaretPosMethodInfo             ,
#endif
    layoutGetCaretPos                       ,


-- ** getCharacterCount #method:getCharacterCount#

#if defined(ENABLE_OVERLOADING)
    LayoutGetCharacterCountMethodInfo       ,
#endif
    layoutGetCharacterCount                 ,


-- ** getContext #method:getContext#

#if defined(ENABLE_OVERLOADING)
    LayoutGetContextMethodInfo              ,
#endif
    layoutGetContext                        ,


-- ** getCursorPos #method:getCursorPos#

#if defined(ENABLE_OVERLOADING)
    LayoutGetCursorPosMethodInfo            ,
#endif
    layoutGetCursorPos                      ,


-- ** getDirection #method:getDirection#

#if defined(ENABLE_OVERLOADING)
    LayoutGetDirectionMethodInfo            ,
#endif
    layoutGetDirection                      ,


-- ** getEllipsize #method:getEllipsize#

#if defined(ENABLE_OVERLOADING)
    LayoutGetEllipsizeMethodInfo            ,
#endif
    layoutGetEllipsize                      ,


-- ** getExtents #method:getExtents#

#if defined(ENABLE_OVERLOADING)
    LayoutGetExtentsMethodInfo              ,
#endif
    layoutGetExtents                        ,


-- ** getFontDescription #method:getFontDescription#

#if defined(ENABLE_OVERLOADING)
    LayoutGetFontDescriptionMethodInfo      ,
#endif
    layoutGetFontDescription                ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    LayoutGetHeightMethodInfo               ,
#endif
    layoutGetHeight                         ,


-- ** getIndent #method:getIndent#

#if defined(ENABLE_OVERLOADING)
    LayoutGetIndentMethodInfo               ,
#endif
    layoutGetIndent                         ,


-- ** getIter #method:getIter#

#if defined(ENABLE_OVERLOADING)
    LayoutGetIterMethodInfo                 ,
#endif
    layoutGetIter                           ,


-- ** getJustify #method:getJustify#

#if defined(ENABLE_OVERLOADING)
    LayoutGetJustifyMethodInfo              ,
#endif
    layoutGetJustify                        ,


-- ** getJustifyLastLine #method:getJustifyLastLine#

#if defined(ENABLE_OVERLOADING)
    LayoutGetJustifyLastLineMethodInfo      ,
#endif
    layoutGetJustifyLastLine                ,


-- ** getLine #method:getLine#

#if defined(ENABLE_OVERLOADING)
    LayoutGetLineMethodInfo                 ,
#endif
    layoutGetLine                           ,


-- ** getLineCount #method:getLineCount#

#if defined(ENABLE_OVERLOADING)
    LayoutGetLineCountMethodInfo            ,
#endif
    layoutGetLineCount                      ,


-- ** getLineReadonly #method:getLineReadonly#

#if defined(ENABLE_OVERLOADING)
    LayoutGetLineReadonlyMethodInfo         ,
#endif
    layoutGetLineReadonly                   ,


-- ** getLineSpacing #method:getLineSpacing#

#if defined(ENABLE_OVERLOADING)
    LayoutGetLineSpacingMethodInfo          ,
#endif
    layoutGetLineSpacing                    ,


-- ** getLines #method:getLines#

#if defined(ENABLE_OVERLOADING)
    LayoutGetLinesMethodInfo                ,
#endif
    layoutGetLines                          ,


-- ** getLinesReadonly #method:getLinesReadonly#

#if defined(ENABLE_OVERLOADING)
    LayoutGetLinesReadonlyMethodInfo        ,
#endif
    layoutGetLinesReadonly                  ,


-- ** getLogAttrs #method:getLogAttrs#

#if defined(ENABLE_OVERLOADING)
    LayoutGetLogAttrsMethodInfo             ,
#endif
    layoutGetLogAttrs                       ,


-- ** getLogAttrsReadonly #method:getLogAttrsReadonly#

#if defined(ENABLE_OVERLOADING)
    LayoutGetLogAttrsReadonlyMethodInfo     ,
#endif
    layoutGetLogAttrsReadonly               ,


-- ** getPixelExtents #method:getPixelExtents#

#if defined(ENABLE_OVERLOADING)
    LayoutGetPixelExtentsMethodInfo         ,
#endif
    layoutGetPixelExtents                   ,


-- ** getPixelSize #method:getPixelSize#

#if defined(ENABLE_OVERLOADING)
    LayoutGetPixelSizeMethodInfo            ,
#endif
    layoutGetPixelSize                      ,


-- ** getSerial #method:getSerial#

#if defined(ENABLE_OVERLOADING)
    LayoutGetSerialMethodInfo               ,
#endif
    layoutGetSerial                         ,


-- ** getSingleParagraphMode #method:getSingleParagraphMode#

#if defined(ENABLE_OVERLOADING)
    LayoutGetSingleParagraphModeMethodInfo  ,
#endif
    layoutGetSingleParagraphMode            ,


-- ** getSize #method:getSize#

#if defined(ENABLE_OVERLOADING)
    LayoutGetSizeMethodInfo                 ,
#endif
    layoutGetSize                           ,


-- ** getSpacing #method:getSpacing#

#if defined(ENABLE_OVERLOADING)
    LayoutGetSpacingMethodInfo              ,
#endif
    layoutGetSpacing                        ,


-- ** getTabs #method:getTabs#

#if defined(ENABLE_OVERLOADING)
    LayoutGetTabsMethodInfo                 ,
#endif
    layoutGetTabs                           ,


-- ** getText #method:getText#

#if defined(ENABLE_OVERLOADING)
    LayoutGetTextMethodInfo                 ,
#endif
    layoutGetText                           ,


-- ** getUnknownGlyphsCount #method:getUnknownGlyphsCount#

#if defined(ENABLE_OVERLOADING)
    LayoutGetUnknownGlyphsCountMethodInfo   ,
#endif
    layoutGetUnknownGlyphsCount             ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    LayoutGetWidthMethodInfo                ,
#endif
    layoutGetWidth                          ,


-- ** getWrap #method:getWrap#

#if defined(ENABLE_OVERLOADING)
    LayoutGetWrapMethodInfo                 ,
#endif
    layoutGetWrap                           ,


-- ** indexToLineX #method:indexToLineX#

#if defined(ENABLE_OVERLOADING)
    LayoutIndexToLineXMethodInfo            ,
#endif
    layoutIndexToLineX                      ,


-- ** indexToPos #method:indexToPos#

#if defined(ENABLE_OVERLOADING)
    LayoutIndexToPosMethodInfo              ,
#endif
    layoutIndexToPos                        ,


-- ** isEllipsized #method:isEllipsized#

#if defined(ENABLE_OVERLOADING)
    LayoutIsEllipsizedMethodInfo            ,
#endif
    layoutIsEllipsized                      ,


-- ** isWrapped #method:isWrapped#

#if defined(ENABLE_OVERLOADING)
    LayoutIsWrappedMethodInfo               ,
#endif
    layoutIsWrapped                         ,


-- ** moveCursorVisually #method:moveCursorVisually#

#if defined(ENABLE_OVERLOADING)
    LayoutMoveCursorVisuallyMethodInfo      ,
#endif
    layoutMoveCursorVisually                ,


-- ** new #method:new#

    layoutNew                               ,


-- ** serialize #method:serialize#

#if defined(ENABLE_OVERLOADING)
    LayoutSerializeMethodInfo               ,
#endif
    layoutSerialize                         ,


-- ** setAlignment #method:setAlignment#

#if defined(ENABLE_OVERLOADING)
    LayoutSetAlignmentMethodInfo            ,
#endif
    layoutSetAlignment                      ,


-- ** setAttributes #method:setAttributes#

#if defined(ENABLE_OVERLOADING)
    LayoutSetAttributesMethodInfo           ,
#endif
    layoutSetAttributes                     ,


-- ** setAutoDir #method:setAutoDir#

#if defined(ENABLE_OVERLOADING)
    LayoutSetAutoDirMethodInfo              ,
#endif
    layoutSetAutoDir                        ,


-- ** setEllipsize #method:setEllipsize#

#if defined(ENABLE_OVERLOADING)
    LayoutSetEllipsizeMethodInfo            ,
#endif
    layoutSetEllipsize                      ,


-- ** setFontDescription #method:setFontDescription#

#if defined(ENABLE_OVERLOADING)
    LayoutSetFontDescriptionMethodInfo      ,
#endif
    layoutSetFontDescription                ,


-- ** setHeight #method:setHeight#

#if defined(ENABLE_OVERLOADING)
    LayoutSetHeightMethodInfo               ,
#endif
    layoutSetHeight                         ,


-- ** setIndent #method:setIndent#

#if defined(ENABLE_OVERLOADING)
    LayoutSetIndentMethodInfo               ,
#endif
    layoutSetIndent                         ,


-- ** setJustify #method:setJustify#

#if defined(ENABLE_OVERLOADING)
    LayoutSetJustifyMethodInfo              ,
#endif
    layoutSetJustify                        ,


-- ** setJustifyLastLine #method:setJustifyLastLine#

#if defined(ENABLE_OVERLOADING)
    LayoutSetJustifyLastLineMethodInfo      ,
#endif
    layoutSetJustifyLastLine                ,


-- ** setLineSpacing #method:setLineSpacing#

#if defined(ENABLE_OVERLOADING)
    LayoutSetLineSpacingMethodInfo          ,
#endif
    layoutSetLineSpacing                    ,


-- ** setMarkup #method:setMarkup#

#if defined(ENABLE_OVERLOADING)
    LayoutSetMarkupMethodInfo               ,
#endif
    layoutSetMarkup                         ,


-- ** setSingleParagraphMode #method:setSingleParagraphMode#

#if defined(ENABLE_OVERLOADING)
    LayoutSetSingleParagraphModeMethodInfo  ,
#endif
    layoutSetSingleParagraphMode            ,


-- ** setSpacing #method:setSpacing#

#if defined(ENABLE_OVERLOADING)
    LayoutSetSpacingMethodInfo              ,
#endif
    layoutSetSpacing                        ,


-- ** setTabs #method:setTabs#

#if defined(ENABLE_OVERLOADING)
    LayoutSetTabsMethodInfo                 ,
#endif
    layoutSetTabs                           ,


-- ** setText #method:setText#

#if defined(ENABLE_OVERLOADING)
    LayoutSetTextMethodInfo                 ,
#endif
    layoutSetText                           ,


-- ** setWidth #method:setWidth#

#if defined(ENABLE_OVERLOADING)
    LayoutSetWidthMethodInfo                ,
#endif
    layoutSetWidth                          ,


-- ** setWrap #method:setWrap#

#if defined(ENABLE_OVERLOADING)
    LayoutSetWrapMethodInfo                 ,
#endif
    layoutSetWrap                           ,


-- ** writeToFile #method:writeToFile#

#if defined(ENABLE_OVERLOADING)
    LayoutWriteToFileMethodInfo             ,
#endif
    layoutWriteToFile                       ,


-- ** xyToIndex #method:xyToIndex#

#if defined(ENABLE_OVERLOADING)
    LayoutXyToIndexMethodInfo               ,
#endif
    layoutXyToIndex                         ,




    ) where

import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Pango.Enums as Pango.Enums
import {-# SOURCE #-} qualified GI.Pango.Flags as Pango.Flags
import {-# SOURCE #-} qualified GI.Pango.Objects.Context as Pango.Context
import {-# SOURCE #-} qualified GI.Pango.Structs.AttrList as Pango.AttrList
import {-# SOURCE #-} qualified GI.Pango.Structs.FontDescription as Pango.FontDescription
import {-# SOURCE #-} qualified GI.Pango.Structs.LayoutIter as Pango.LayoutIter
import {-# SOURCE #-} qualified GI.Pango.Structs.LayoutLine as Pango.LayoutLine
import {-# SOURCE #-} qualified GI.Pango.Structs.LogAttr as Pango.LogAttr
import {-# SOURCE #-} qualified GI.Pango.Structs.Rectangle as Pango.Rectangle
import {-# SOURCE #-} qualified GI.Pango.Structs.TabArray as Pango.TabArray

-- | Memory-managed wrapper type.
newtype Layout = Layout (SP.ManagedPtr Layout)
    deriving (Layout -> Layout -> Bool
(Layout -> Layout -> Bool)
-> (Layout -> Layout -> Bool) -> Eq Layout
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Layout -> Layout -> Bool
$c/= :: Layout -> Layout -> Bool
== :: Layout -> Layout -> Bool
$c== :: Layout -> Layout -> Bool
Eq)

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

foreign import ccall "pango_layout_get_type"
    c_pango_layout_get_type :: IO B.Types.GType

instance B.Types.TypedObject Layout where
    glibType :: IO GType
glibType = IO GType
c_pango_layout_get_type

instance B.Types.GObject Layout

-- | Type class for types which can be safely cast to `Layout`, for instance with `toLayout`.
class (SP.GObject o, O.IsDescendantOf Layout o) => IsLayout o
instance (SP.GObject o, O.IsDescendantOf Layout o) => IsLayout o

instance O.HasParentTypes Layout
type instance O.ParentTypes Layout = '[GObject.Object.Object]

-- | Cast to `Layout`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toLayout :: (MIO.MonadIO m, IsLayout o) => o -> m Layout
toLayout :: forall (m :: * -> *) o. (MonadIO m, IsLayout o) => o -> m Layout
toLayout = IO Layout -> m Layout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Layout -> m Layout) -> (o -> IO Layout) -> o -> m Layout
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Layout -> Layout) -> o -> IO Layout
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Layout -> Layout
Layout

-- | Convert 'Layout' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue (Maybe Layout) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_pango_layout_get_type
    gvalueSet_ :: Ptr GValue -> Maybe Layout -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Layout
P.Nothing = Ptr GValue -> Ptr Layout -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Layout
forall a. Ptr a
FP.nullPtr :: FP.Ptr Layout)
    gvalueSet_ Ptr GValue
gv (P.Just Layout
obj) = Layout -> (Ptr Layout -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Layout
obj (Ptr GValue -> Ptr Layout -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe Layout)
gvalueGet_ Ptr GValue
gv = do
        Ptr Layout
ptr <- Ptr GValue -> IO (Ptr Layout)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Layout)
        if Ptr Layout
ptr Ptr Layout -> Ptr Layout -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr Layout
forall a. Ptr a
FP.nullPtr
        then Layout -> Maybe Layout
forall a. a -> Maybe a
P.Just (Layout -> Maybe Layout) -> IO Layout -> IO (Maybe Layout)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr Layout -> Layout) -> Ptr Layout -> IO Layout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr Layout -> Layout
Layout Ptr Layout
ptr
        else Maybe Layout -> IO (Maybe Layout)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Layout
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveLayoutMethod (t :: Symbol) (o :: *) :: * where
    ResolveLayoutMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveLayoutMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveLayoutMethod "contextChanged" o = LayoutContextChangedMethodInfo
    ResolveLayoutMethod "copy" o = LayoutCopyMethodInfo
    ResolveLayoutMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveLayoutMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveLayoutMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveLayoutMethod "indexToLineX" o = LayoutIndexToLineXMethodInfo
    ResolveLayoutMethod "indexToPos" o = LayoutIndexToPosMethodInfo
    ResolveLayoutMethod "isEllipsized" o = LayoutIsEllipsizedMethodInfo
    ResolveLayoutMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveLayoutMethod "isWrapped" o = LayoutIsWrappedMethodInfo
    ResolveLayoutMethod "moveCursorVisually" o = LayoutMoveCursorVisuallyMethodInfo
    ResolveLayoutMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveLayoutMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveLayoutMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveLayoutMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveLayoutMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveLayoutMethod "serialize" o = LayoutSerializeMethodInfo
    ResolveLayoutMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveLayoutMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveLayoutMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveLayoutMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveLayoutMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveLayoutMethod "writeToFile" o = LayoutWriteToFileMethodInfo
    ResolveLayoutMethod "xyToIndex" o = LayoutXyToIndexMethodInfo
    ResolveLayoutMethod "getAlignment" o = LayoutGetAlignmentMethodInfo
    ResolveLayoutMethod "getAttributes" o = LayoutGetAttributesMethodInfo
    ResolveLayoutMethod "getAutoDir" o = LayoutGetAutoDirMethodInfo
    ResolveLayoutMethod "getBaseline" o = LayoutGetBaselineMethodInfo
    ResolveLayoutMethod "getCaretPos" o = LayoutGetCaretPosMethodInfo
    ResolveLayoutMethod "getCharacterCount" o = LayoutGetCharacterCountMethodInfo
    ResolveLayoutMethod "getContext" o = LayoutGetContextMethodInfo
    ResolveLayoutMethod "getCursorPos" o = LayoutGetCursorPosMethodInfo
    ResolveLayoutMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveLayoutMethod "getDirection" o = LayoutGetDirectionMethodInfo
    ResolveLayoutMethod "getEllipsize" o = LayoutGetEllipsizeMethodInfo
    ResolveLayoutMethod "getExtents" o = LayoutGetExtentsMethodInfo
    ResolveLayoutMethod "getFontDescription" o = LayoutGetFontDescriptionMethodInfo
    ResolveLayoutMethod "getHeight" o = LayoutGetHeightMethodInfo
    ResolveLayoutMethod "getIndent" o = LayoutGetIndentMethodInfo
    ResolveLayoutMethod "getIter" o = LayoutGetIterMethodInfo
    ResolveLayoutMethod "getJustify" o = LayoutGetJustifyMethodInfo
    ResolveLayoutMethod "getJustifyLastLine" o = LayoutGetJustifyLastLineMethodInfo
    ResolveLayoutMethod "getLine" o = LayoutGetLineMethodInfo
    ResolveLayoutMethod "getLineCount" o = LayoutGetLineCountMethodInfo
    ResolveLayoutMethod "getLineReadonly" o = LayoutGetLineReadonlyMethodInfo
    ResolveLayoutMethod "getLineSpacing" o = LayoutGetLineSpacingMethodInfo
    ResolveLayoutMethod "getLines" o = LayoutGetLinesMethodInfo
    ResolveLayoutMethod "getLinesReadonly" o = LayoutGetLinesReadonlyMethodInfo
    ResolveLayoutMethod "getLogAttrs" o = LayoutGetLogAttrsMethodInfo
    ResolveLayoutMethod "getLogAttrsReadonly" o = LayoutGetLogAttrsReadonlyMethodInfo
    ResolveLayoutMethod "getPixelExtents" o = LayoutGetPixelExtentsMethodInfo
    ResolveLayoutMethod "getPixelSize" o = LayoutGetPixelSizeMethodInfo
    ResolveLayoutMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveLayoutMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveLayoutMethod "getSerial" o = LayoutGetSerialMethodInfo
    ResolveLayoutMethod "getSingleParagraphMode" o = LayoutGetSingleParagraphModeMethodInfo
    ResolveLayoutMethod "getSize" o = LayoutGetSizeMethodInfo
    ResolveLayoutMethod "getSpacing" o = LayoutGetSpacingMethodInfo
    ResolveLayoutMethod "getTabs" o = LayoutGetTabsMethodInfo
    ResolveLayoutMethod "getText" o = LayoutGetTextMethodInfo
    ResolveLayoutMethod "getUnknownGlyphsCount" o = LayoutGetUnknownGlyphsCountMethodInfo
    ResolveLayoutMethod "getWidth" o = LayoutGetWidthMethodInfo
    ResolveLayoutMethod "getWrap" o = LayoutGetWrapMethodInfo
    ResolveLayoutMethod "setAlignment" o = LayoutSetAlignmentMethodInfo
    ResolveLayoutMethod "setAttributes" o = LayoutSetAttributesMethodInfo
    ResolveLayoutMethod "setAutoDir" o = LayoutSetAutoDirMethodInfo
    ResolveLayoutMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveLayoutMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveLayoutMethod "setEllipsize" o = LayoutSetEllipsizeMethodInfo
    ResolveLayoutMethod "setFontDescription" o = LayoutSetFontDescriptionMethodInfo
    ResolveLayoutMethod "setHeight" o = LayoutSetHeightMethodInfo
    ResolveLayoutMethod "setIndent" o = LayoutSetIndentMethodInfo
    ResolveLayoutMethod "setJustify" o = LayoutSetJustifyMethodInfo
    ResolveLayoutMethod "setJustifyLastLine" o = LayoutSetJustifyLastLineMethodInfo
    ResolveLayoutMethod "setLineSpacing" o = LayoutSetLineSpacingMethodInfo
    ResolveLayoutMethod "setMarkup" o = LayoutSetMarkupMethodInfo
    ResolveLayoutMethod "setMarkupWithAccel" o = LayoutSetMarkupWithAccelMethodInfo
    ResolveLayoutMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveLayoutMethod "setSingleParagraphMode" o = LayoutSetSingleParagraphModeMethodInfo
    ResolveLayoutMethod "setSpacing" o = LayoutSetSpacingMethodInfo
    ResolveLayoutMethod "setTabs" o = LayoutSetTabsMethodInfo
    ResolveLayoutMethod "setText" o = LayoutSetTextMethodInfo
    ResolveLayoutMethod "setWidth" o = LayoutSetWidthMethodInfo
    ResolveLayoutMethod "setWrap" o = LayoutSetWrapMethodInfo
    ResolveLayoutMethod l o = O.MethodResolutionFailed l o

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

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolveLayoutMethod t Layout, O.OverloadedMethod info Layout p, R.HasField t Layout p) => R.HasField t Layout p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveLayoutMethod t Layout, O.OverloadedMethodInfo info Layout) => OL.IsLabel t (O.MethodProxy info Layout) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Layout = LayoutSignalList
type LayoutSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method Layout::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Context" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Layout" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_new" pango_layout_new :: 
    Ptr Pango.Context.Context ->            -- context : TInterface (Name {namespace = "Pango", name = "Context"})
    IO (Ptr Layout)

-- | Create a new @PangoLayout@ object with attributes initialized to
-- default values for a particular @PangoContext@.
layoutNew ::
    (B.CallStack.HasCallStack, MonadIO m, Pango.Context.IsContext a) =>
    a
    -- ^ /@context@/: a @PangoContext@
    -> m Layout
    -- ^ __Returns:__ the newly allocated @PangoLayout@
layoutNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContext a) =>
a -> m Layout
layoutNew a
context = IO Layout -> m Layout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Layout -> m Layout) -> IO Layout -> m Layout
forall a b. (a -> b) -> a -> b
$ do
    Ptr Context
context' <- a -> IO (Ptr Context)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Layout
result <- Ptr Context -> IO (Ptr Layout)
pango_layout_new Ptr Context
context'
    Text -> Ptr Layout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"layoutNew" Ptr Layout
result
    Layout
result' <- ((ManagedPtr Layout -> Layout) -> Ptr Layout -> IO Layout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Layout -> Layout
Layout) Ptr Layout
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Layout -> IO Layout
forall (m :: * -> *) a. Monad m => a -> m a
return Layout
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method Layout::context_changed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , 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_context_changed" pango_layout_context_changed :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO ()

-- | Forces recomputation of any state in the @PangoLayout@ that
-- might depend on the layout\'s context.
-- 
-- This function should be called if you make changes to the context
-- subsequent to creating the layout.
layoutContextChanged ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m ()
layoutContextChanged :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m ()
layoutContextChanged a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Layout -> IO ()
pango_layout_context_changed Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutContextChangedMethodInfo
instance (signature ~ (m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutContextChangedMethodInfo a signature where
    overloadedMethod = layoutContextChanged

instance O.OverloadedMethodInfo LayoutContextChangedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutContextChanged",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutContextChanged"
        })


#endif

-- method Layout::copy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "src"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Layout" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_copy" pango_layout_copy :: 
    Ptr Layout ->                           -- src : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO (Ptr Layout)

-- | Creates a deep copy-by-value of the layout.
-- 
-- The attribute list, tab array, and text from the original layout
-- are all copied by value.
layoutCopy ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@src@/: a @PangoLayout@
    -> m Layout
    -- ^ __Returns:__ the newly allocated @PangoLayout@
layoutCopy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Layout
layoutCopy a
src = IO Layout -> m Layout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Layout -> m Layout) -> IO Layout -> m Layout
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
src' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
src
    Ptr Layout
result <- Ptr Layout -> IO (Ptr Layout)
pango_layout_copy Ptr Layout
src'
    Text -> Ptr Layout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"layoutCopy" Ptr Layout
result
    Layout
result' <- ((ManagedPtr Layout -> Layout) -> Ptr Layout -> IO Layout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Layout -> Layout
Layout) Ptr Layout
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
src
    Layout -> IO Layout
forall (m :: * -> *) a. Monad m => a -> m a
return Layout
result'

#if defined(ENABLE_OVERLOADING)
data LayoutCopyMethodInfo
instance (signature ~ (m Layout), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutCopyMethodInfo a signature where
    overloadedMethod = layoutCopy

instance O.OverloadedMethodInfo LayoutCopyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutCopy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutCopy"
        })


#endif

-- method Layout::get_alignment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Alignment" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_alignment" pango_layout_get_alignment :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CUInt

-- | Gets the alignment for the layout: how partial lines are
-- positioned within the horizontal space available.
layoutGetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Pango.Enums.Alignment
    -- ^ __Returns:__ the alignment
layoutGetAlignment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Alignment
layoutGetAlignment a
layout = IO Alignment -> m Alignment
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Alignment -> m Alignment) -> IO Alignment -> m Alignment
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CUInt
result <- Ptr Layout -> IO CUInt
pango_layout_get_alignment Ptr Layout
layout'
    let result' :: Alignment
result' = (Int -> Alignment
forall a. Enum a => Int -> a
toEnum (Int -> Alignment) -> (CUInt -> Int) -> CUInt -> Alignment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Alignment -> IO Alignment
forall (m :: * -> *) a. Monad m => a -> m a
return Alignment
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetAlignmentMethodInfo
instance (signature ~ (m Pango.Enums.Alignment), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetAlignmentMethodInfo a signature where
    overloadedMethod = layoutGetAlignment

instance O.OverloadedMethodInfo LayoutGetAlignmentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetAlignment",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetAlignment"
        })


#endif

-- method Layout::get_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "AttrList" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_attributes" pango_layout_get_attributes :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO (Ptr Pango.AttrList.AttrList)

-- | Gets the attribute list for the layout, if any.
layoutGetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m (Maybe Pango.AttrList.AttrList)
    -- ^ __Returns:__ a @PangoAttrList@
layoutGetAttributes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m (Maybe AttrList)
layoutGetAttributes a
layout = IO (Maybe AttrList) -> m (Maybe AttrList)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe AttrList) -> m (Maybe AttrList))
-> IO (Maybe AttrList) -> m (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr AttrList
result <- Ptr Layout -> IO (Ptr AttrList)
pango_layout_get_attributes Ptr Layout
layout'
    Maybe AttrList
maybeResult <- Ptr AttrList
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr AttrList
result ((Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList))
-> (Ptr AttrList -> IO AttrList) -> IO (Maybe AttrList)
forall a b. (a -> b) -> a -> b
$ \Ptr AttrList
result' -> do
        AttrList
result'' <- ((ManagedPtr AttrList -> AttrList) -> Ptr AttrList -> IO AttrList
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr AttrList -> AttrList
Pango.AttrList.AttrList) Ptr AttrList
result'
        AttrList -> IO AttrList
forall (m :: * -> *) a. Monad m => a -> m a
return AttrList
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Maybe AttrList -> IO (Maybe AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe AttrList
maybeResult

#if defined(ENABLE_OVERLOADING)
data LayoutGetAttributesMethodInfo
instance (signature ~ (m (Maybe Pango.AttrList.AttrList)), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetAttributesMethodInfo a signature where
    overloadedMethod = layoutGetAttributes

instance O.OverloadedMethodInfo LayoutGetAttributesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetAttributes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetAttributes"
        })


#endif

-- method Layout::get_auto_dir
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_auto_dir" pango_layout_get_auto_dir :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CInt

-- | Gets whether to calculate the base direction for the layout
-- according to its contents.
-- 
-- See 'GI.Pango.Objects.Layout.layoutSetAutoDir'.
-- 
-- /Since: 1.4/
layoutGetAutoDir ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the bidirectional base direction
    --   is computed from the layout\'s contents, 'P.False' otherwise
layoutGetAutoDir :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Bool
layoutGetAutoDir a
layout = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr Layout -> IO CInt
pango_layout_get_auto_dir Ptr Layout
layout'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetAutoDirMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetAutoDirMethodInfo a signature where
    overloadedMethod = layoutGetAutoDir

instance O.OverloadedMethodInfo LayoutGetAutoDirMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetAutoDir",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetAutoDir"
        })


#endif

-- method Layout::get_baseline
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_baseline" pango_layout_get_baseline :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO Int32

-- | Gets the Y position of baseline of the first line in /@layout@/.
-- 
-- /Since: 1.22/
layoutGetBaseline ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Int32
    -- ^ __Returns:__ baseline of first line, from top of /@layout@/
layoutGetBaseline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Int32
layoutGetBaseline a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr Layout -> IO Int32
pango_layout_get_baseline Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data LayoutGetBaselineMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetBaselineMethodInfo a signature where
    overloadedMethod = layoutGetBaseline

instance O.OverloadedMethodInfo LayoutGetBaselineMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetBaseline",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetBaseline"
        })


#endif

-- method Layout::get_caret_pos
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , 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 "the byte index of the cursor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "strong_pos"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the strong cursor position"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "weak_pos"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the weak cursor position"
--                 , 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_get_caret_pos" pango_layout_get_caret_pos :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- index_ : TBasicType TInt
    Ptr Pango.Rectangle.Rectangle ->        -- strong_pos : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    Ptr Pango.Rectangle.Rectangle ->        -- weak_pos : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    IO ()

-- | Given an index within a layout, determines the positions that of the
-- strong and weak cursors if the insertion point is at that index.
-- 
-- This is a variant of 'GI.Pango.Objects.Layout.layoutGetCursorPos' that applies
-- font metric information about caret slope and offset to the positions
-- it returns.
-- 
-- \<picture>
--   \<source srcset=\"caret-metrics-dark.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img alt=\"Caret metrics\" src=\"caret-metrics-light.png\">
-- \<\/picture>
-- 
-- /Since: 1.50/
layoutGetCaretPos ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@index_@/: the byte index of the cursor
    -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutGetCaretPos :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m (Rectangle, Rectangle)
layoutGetCaretPos a
layout Int32
index_ = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Rectangle
strongPos <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
16 :: IO (Ptr Pango.Rectangle.Rectangle)
    Ptr Rectangle
weakPos <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
16 :: IO (Ptr Pango.Rectangle.Rectangle)
    Ptr Layout -> Int32 -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_get_caret_pos Ptr Layout
layout' Int32
index_ Ptr Rectangle
strongPos Ptr Rectangle
weakPos
    Rectangle
strongPos' <- ((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
strongPos
    Rectangle
weakPos' <- ((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
weakPos
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    (Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
strongPos', Rectangle
weakPos')

#if defined(ENABLE_OVERLOADING)
data LayoutGetCaretPosMethodInfo
instance (signature ~ (Int32 -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetCaretPosMethodInfo a signature where
    overloadedMethod = layoutGetCaretPos

instance O.OverloadedMethodInfo LayoutGetCaretPosMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetCaretPos",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetCaretPos"
        })


#endif

-- method Layout::get_character_count
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_character_count" pango_layout_get_character_count :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO Int32

-- | Returns the number of Unicode characters in the
-- the text of /@layout@/.
-- 
-- /Since: 1.30/
layoutGetCharacterCount ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Int32
    -- ^ __Returns:__ the number of Unicode characters
    --   in the text of /@layout@/
layoutGetCharacterCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Int32
layoutGetCharacterCount a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr Layout -> IO Int32
pango_layout_get_character_count Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data LayoutGetCharacterCountMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetCharacterCountMethodInfo a signature where
    overloadedMethod = layoutGetCharacterCount

instance O.OverloadedMethodInfo LayoutGetCharacterCountMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetCharacterCount",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetCharacterCount"
        })


#endif

-- method Layout::get_context
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Context" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_context" pango_layout_get_context :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO (Ptr Pango.Context.Context)

-- | Retrieves the @PangoContext@ used for this layout.
layoutGetContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Pango.Context.Context
    -- ^ __Returns:__ the @PangoContext@ for the layout
layoutGetContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Context
layoutGetContext a
layout = IO Context -> m Context
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Context -> m Context) -> IO Context -> m Context
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Context
result <- Ptr Layout -> IO (Ptr Context)
pango_layout_get_context Ptr Layout
layout'
    Text -> Ptr Context -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"layoutGetContext" Ptr Context
result
    Context
result' <- ((ManagedPtr Context -> Context) -> Ptr Context -> IO Context
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Context -> Context
Pango.Context.Context) Ptr Context
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Context -> IO Context
forall (m :: * -> *) a. Monad m => a -> m a
return Context
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetContextMethodInfo
instance (signature ~ (m Pango.Context.Context), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetContextMethodInfo a signature where
    overloadedMethod = layoutGetContext

instance O.OverloadedMethodInfo LayoutGetContextMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetContext",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetContext"
        })


#endif

-- method Layout::get_cursor_pos
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , 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 "the byte index of the cursor"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "strong_pos"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the strong cursor position"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = True
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "weak_pos"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the weak cursor position"
--                 , 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_get_cursor_pos" pango_layout_get_cursor_pos :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- index_ : TBasicType TInt
    Ptr Pango.Rectangle.Rectangle ->        -- strong_pos : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    Ptr Pango.Rectangle.Rectangle ->        -- weak_pos : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    IO ()

-- | Given an index within a layout, determines the positions that of the
-- strong and weak cursors if the insertion point is at that index.
-- 
-- The position of each cursor is stored as a zero-width rectangle
-- with the height of the run extents.
-- 
-- \<picture>
--   \<source srcset=\"cursor-positions-dark.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img alt=\"Cursor positions\" src=\"cursor-positions-light.png\">
-- \<\/picture>
-- 
-- The strong cursor location is the location where characters of the
-- directionality equal to the base direction of the layout are inserted.
-- The weak cursor location is the location where characters of the
-- directionality opposite to the base direction of the layout are inserted.
-- 
-- The following example shows text with both a strong and a weak cursor.
-- 
-- \<picture>
--   \<source srcset=\"split-cursor-dark.png\" media=\"(prefers-color-scheme: dark)\">
--   \<img alt=\"Strong and weak cursors\" src=\"split-cursor-light.png\">
-- \<\/picture>
-- 
-- The strong cursor has a little arrow pointing to the right, the weak
-- cursor to the left. Typing a \'c\' in this situation will insert the
-- character after the \'b\', and typing another Hebrew character, like \'ג\',
-- will insert it at the end.
layoutGetCursorPos ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@index_@/: the byte index of the cursor
    -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutGetCursorPos :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m (Rectangle, Rectangle)
layoutGetCursorPos a
layout Int32
index_ = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Rectangle
strongPos <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
16 :: IO (Ptr Pango.Rectangle.Rectangle)
    Ptr Rectangle
weakPos <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
16 :: IO (Ptr Pango.Rectangle.Rectangle)
    Ptr Layout -> Int32 -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_get_cursor_pos Ptr Layout
layout' Int32
index_ Ptr Rectangle
strongPos Ptr Rectangle
weakPos
    Rectangle
strongPos' <- ((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
strongPos
    Rectangle
weakPos' <- ((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
weakPos
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    (Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
strongPos', Rectangle
weakPos')

#if defined(ENABLE_OVERLOADING)
data LayoutGetCursorPosMethodInfo
instance (signature ~ (Int32 -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetCursorPosMethodInfo a signature where
    overloadedMethod = layoutGetCursorPos

instance O.OverloadedMethodInfo LayoutGetCursorPosMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetCursorPos",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetCursorPos"
        })


#endif

-- method Layout::get_direction
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , 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 "the byte index of the char"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Direction" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_direction" pango_layout_get_direction :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- index : TBasicType TInt
    IO CUInt

-- | Gets the text direction at the given character position in /@layout@/.
-- 
-- /Since: 1.46/
layoutGetDirection ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@index@/: the byte index of the char
    -> m Pango.Enums.Direction
    -- ^ __Returns:__ the text direction at /@index@/
layoutGetDirection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m Direction
layoutGetDirection a
layout Int32
index = IO Direction -> m Direction
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Direction -> m Direction) -> IO Direction -> m Direction
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CUInt
result <- Ptr Layout -> Int32 -> IO CUInt
pango_layout_get_direction Ptr Layout
layout' Int32
index
    let result' :: Direction
result' = (Int -> Direction
forall a. Enum a => Int -> a
toEnum (Int -> Direction) -> (CUInt -> Int) -> CUInt -> Direction
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Direction -> IO Direction
forall (m :: * -> *) a. Monad m => a -> m a
return Direction
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetDirectionMethodInfo
instance (signature ~ (Int32 -> m Pango.Enums.Direction), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetDirectionMethodInfo a signature where
    overloadedMethod = layoutGetDirection

instance O.OverloadedMethodInfo LayoutGetDirectionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetDirection",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetDirection"
        })


#endif

-- method Layout::get_ellipsize
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Pango" , name = "EllipsizeMode" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_ellipsize" pango_layout_get_ellipsize :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CUInt

-- | Gets the type of ellipsization being performed for /@layout@/.
-- 
-- See 'GI.Pango.Objects.Layout.layoutSetEllipsize'.
-- 
-- Use 'GI.Pango.Objects.Layout.layoutIsEllipsized' to query whether any
-- paragraphs were actually ellipsized.
-- 
-- /Since: 1.6/
layoutGetEllipsize ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Pango.Enums.EllipsizeMode
    -- ^ __Returns:__ the current ellipsization mode for /@layout@/
layoutGetEllipsize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m EllipsizeMode
layoutGetEllipsize a
layout = IO EllipsizeMode -> m EllipsizeMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO EllipsizeMode -> m EllipsizeMode)
-> IO EllipsizeMode -> m EllipsizeMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CUInt
result <- Ptr Layout -> IO CUInt
pango_layout_get_ellipsize Ptr Layout
layout'
    let result' :: EllipsizeMode
result' = (Int -> EllipsizeMode
forall a. Enum a => Int -> a
toEnum (Int -> EllipsizeMode) -> (CUInt -> Int) -> CUInt -> EllipsizeMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    EllipsizeMode -> IO EllipsizeMode
forall (m :: * -> *) a. Monad m => a -> m a
return EllipsizeMode
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetEllipsizeMethodInfo
instance (signature ~ (m Pango.Enums.EllipsizeMode), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetEllipsizeMethodInfo a signature where
    overloadedMethod = layoutGetEllipsize

instance O.OverloadedMethodInfo LayoutGetEllipsizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetEllipsize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetEllipsize"
        })


#endif

-- method Layout::get_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , 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 the\n  layout as drawn"
--                 , 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 layout"
--                 , 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_get_extents" pango_layout_get_extents :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    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 /@layout@/.
-- 
-- Logical extents are usually what you want for positioning things. Note
-- that both extents may have non-zero x and y. You may want to use those
-- to offset where you render the layout. Not doing that is a very typical
-- bug that shows up as right-to-left layouts not being correctly positioned
-- in a layout with a set width.
-- 
-- The extents are given in layout coordinates and in Pango units; layout
-- coordinates begin at the top left corner of the layout.
layoutGetExtents ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutGetExtents :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m (Rectangle, Rectangle)
layoutGetExtents a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    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 Layout -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_get_extents Ptr Layout
layout' 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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    (Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
inkRect', Rectangle
logicalRect')

#if defined(ENABLE_OVERLOADING)
data LayoutGetExtentsMethodInfo
instance (signature ~ (m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetExtentsMethodInfo a signature where
    overloadedMethod = layoutGetExtents

instance O.OverloadedMethodInfo LayoutGetExtentsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetExtents",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetExtents"
        })


#endif

-- method Layout::get_font_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "Pango" , name = "FontDescription" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_font_description" pango_layout_get_font_description :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO (Ptr Pango.FontDescription.FontDescription)

-- | Gets the font description for the layout, if any.
-- 
-- /Since: 1.8/
layoutGetFontDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m (Maybe Pango.FontDescription.FontDescription)
    -- ^ __Returns:__ a pointer to the
    --   layout\'s font description, or 'P.Nothing' if the font description
    --   from the layout\'s context is inherited.
layoutGetFontDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m (Maybe FontDescription)
layoutGetFontDescription a
layout = IO (Maybe FontDescription) -> m (Maybe FontDescription)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe FontDescription) -> m (Maybe FontDescription))
-> IO (Maybe FontDescription) -> m (Maybe FontDescription)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr FontDescription
result <- Ptr Layout -> IO (Ptr FontDescription)
pango_layout_get_font_description Ptr Layout
layout'
    Maybe FontDescription
maybeResult <- Ptr FontDescription
-> (Ptr FontDescription -> IO FontDescription)
-> IO (Maybe FontDescription)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr FontDescription
result ((Ptr FontDescription -> IO FontDescription)
 -> IO (Maybe FontDescription))
-> (Ptr FontDescription -> IO FontDescription)
-> IO (Maybe FontDescription)
forall a b. (a -> b) -> a -> b
$ \Ptr FontDescription
result' -> do
        FontDescription
result'' <- ((ManagedPtr FontDescription -> FontDescription)
-> Ptr FontDescription -> IO FontDescription
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr FontDescription -> FontDescription
Pango.FontDescription.FontDescription) Ptr FontDescription
result'
        FontDescription -> IO FontDescription
forall (m :: * -> *) a. Monad m => a -> m a
return FontDescription
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Maybe FontDescription -> IO (Maybe FontDescription)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe FontDescription
maybeResult

#if defined(ENABLE_OVERLOADING)
data LayoutGetFontDescriptionMethodInfo
instance (signature ~ (m (Maybe Pango.FontDescription.FontDescription)), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetFontDescriptionMethodInfo a signature where
    overloadedMethod = layoutGetFontDescription

instance O.OverloadedMethodInfo LayoutGetFontDescriptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetFontDescription",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetFontDescription"
        })


#endif

-- method Layout::get_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_height" pango_layout_get_height :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO Int32

-- | Gets the height of layout used for ellipsization.
-- 
-- See 'GI.Pango.Objects.Layout.layoutSetHeight' for details.
-- 
-- /Since: 1.20/
layoutGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Int32
    -- ^ __Returns:__ the height, in Pango units if positive,
    --   or number of lines if negative.
layoutGetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Int32
layoutGetHeight a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr Layout -> IO Int32
pango_layout_get_height Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data LayoutGetHeightMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetHeightMethodInfo a signature where
    overloadedMethod = layoutGetHeight

instance O.OverloadedMethodInfo LayoutGetHeightMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetHeight",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetHeight"
        })


#endif

-- method Layout::get_indent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_indent" pango_layout_get_indent :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO Int32

-- | Gets the paragraph indent width in Pango units.
-- 
-- A negative value indicates a hanging indentation.
layoutGetIndent ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Int32
    -- ^ __Returns:__ the indent in Pango units
layoutGetIndent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Int32
layoutGetIndent a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr Layout -> IO Int32
pango_layout_get_indent Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data LayoutGetIndentMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetIndentMethodInfo a signature where
    overloadedMethod = layoutGetIndent

instance O.OverloadedMethodInfo LayoutGetIndentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetIndent",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetIndent"
        })


#endif

-- method Layout::get_iter
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Pango" , name = "LayoutIter" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_iter" pango_layout_get_iter :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO (Ptr Pango.LayoutIter.LayoutIter)

-- | Returns an iterator to iterate over the visual extents of the layout.
layoutGetIter ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Pango.LayoutIter.LayoutIter
    -- ^ __Returns:__ the new @PangoLayoutIter@
layoutGetIter :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m LayoutIter
layoutGetIter a
layout = IO LayoutIter -> m LayoutIter
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO LayoutIter -> m LayoutIter) -> IO LayoutIter -> m LayoutIter
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr LayoutIter
result <- Ptr Layout -> IO (Ptr LayoutIter)
pango_layout_get_iter Ptr Layout
layout'
    Text -> Ptr LayoutIter -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"layoutGetIter" Ptr LayoutIter
result
    LayoutIter
result' <- ((ManagedPtr LayoutIter -> LayoutIter)
-> Ptr LayoutIter -> IO LayoutIter
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr LayoutIter -> LayoutIter
Pango.LayoutIter.LayoutIter) Ptr LayoutIter
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    LayoutIter -> IO LayoutIter
forall (m :: * -> *) a. Monad m => a -> m a
return LayoutIter
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetIterMethodInfo
instance (signature ~ (m Pango.LayoutIter.LayoutIter), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetIterMethodInfo a signature where
    overloadedMethod = layoutGetIter

instance O.OverloadedMethodInfo LayoutGetIterMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetIter",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetIter"
        })


#endif

-- method Layout::get_justify
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_justify" pango_layout_get_justify :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CInt

-- | Gets whether each complete line should be stretched to fill the entire
-- width of the layout.
layoutGetJustify ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Bool
    -- ^ __Returns:__ the justify value
layoutGetJustify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Bool
layoutGetJustify a
layout = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr Layout -> IO CInt
pango_layout_get_justify Ptr Layout
layout'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetJustifyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetJustifyMethodInfo a signature where
    overloadedMethod = layoutGetJustify

instance O.OverloadedMethodInfo LayoutGetJustifyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetJustify",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetJustify"
        })


#endif

-- method Layout::get_justify_last_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_justify_last_line" pango_layout_get_justify_last_line :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CInt

-- | Gets whether the last line should be stretched
-- to fill the entire width of the layout.
-- 
-- /Since: 1.50/
layoutGetJustifyLastLine ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Bool
    -- ^ __Returns:__ the justify value
layoutGetJustifyLastLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Bool
layoutGetJustifyLastLine a
layout = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr Layout -> IO CInt
pango_layout_get_justify_last_line Ptr Layout
layout'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetJustifyLastLineMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetJustifyLastLineMethodInfo a signature where
    overloadedMethod = layoutGetJustifyLastLine

instance O.OverloadedMethodInfo LayoutGetJustifyLastLineMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetJustifyLastLine",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetJustifyLastLine"
        })


#endif

-- method Layout::get_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "line"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the index of a line, which must be between 0 and\n  `pango_layout_get_line_count(layout) - 1`, inclusive."
--                 , 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_get_line" pango_layout_get_line :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- line : TBasicType TInt
    IO (Ptr Pango.LayoutLine.LayoutLine)

-- | Retrieves a particular line from a @PangoLayout@.
-- 
-- Use the faster 'GI.Pango.Objects.Layout.layoutGetLineReadonly' if you do not
-- plan to modify the contents of the line (glyphs, glyph widths, etc.).
layoutGetLine ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@line@/: the index of a line, which must be between 0 and
    --   @pango_layout_get_line_count(layout) - 1@, inclusive.
    -> m (Maybe Pango.LayoutLine.LayoutLine)
    -- ^ __Returns:__ the requested @PangoLayoutLine@,
    --   or 'P.Nothing' if the index is out of range. This layout line can be ref\'ed
    --   and retained, but will become invalid if changes are made to the
    --   @PangoLayout@.
layoutGetLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m (Maybe LayoutLine)
layoutGetLine a
layout Int32
line = IO (Maybe LayoutLine) -> m (Maybe LayoutLine)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe LayoutLine) -> m (Maybe LayoutLine))
-> IO (Maybe LayoutLine) -> m (Maybe LayoutLine)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr LayoutLine
result <- Ptr Layout -> Int32 -> IO (Ptr LayoutLine)
pango_layout_get_line Ptr Layout
layout' Int32
line
    Maybe LayoutLine
maybeResult <- Ptr LayoutLine
-> (Ptr LayoutLine -> IO LayoutLine) -> IO (Maybe LayoutLine)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr LayoutLine
result ((Ptr LayoutLine -> IO LayoutLine) -> IO (Maybe LayoutLine))
-> (Ptr LayoutLine -> IO LayoutLine) -> IO (Maybe LayoutLine)
forall a b. (a -> b) -> a -> b
$ \Ptr LayoutLine
result' -> do
        LayoutLine
result'' <- ((ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr LayoutLine -> LayoutLine
Pango.LayoutLine.LayoutLine) Ptr LayoutLine
result'
        LayoutLine -> IO LayoutLine
forall (m :: * -> *) a. Monad m => a -> m a
return LayoutLine
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Maybe LayoutLine -> IO (Maybe LayoutLine)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LayoutLine
maybeResult

#if defined(ENABLE_OVERLOADING)
data LayoutGetLineMethodInfo
instance (signature ~ (Int32 -> m (Maybe Pango.LayoutLine.LayoutLine)), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetLineMethodInfo a signature where
    overloadedMethod = layoutGetLine

instance O.OverloadedMethodInfo LayoutGetLineMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetLine",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetLine"
        })


#endif

-- method Layout::get_line_count
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_line_count" pango_layout_get_line_count :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO Int32

-- | Retrieves the count of lines for the /@layout@/.
layoutGetLineCount ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: @PangoLayout@
    -> m Int32
    -- ^ __Returns:__ the line count
layoutGetLineCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Int32
layoutGetLineCount a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr Layout -> IO Int32
pango_layout_get_line_count Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data LayoutGetLineCountMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetLineCountMethodInfo a signature where
    overloadedMethod = layoutGetLineCount

instance O.OverloadedMethodInfo LayoutGetLineCountMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetLineCount",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetLineCount"
        })


#endif

-- method Layout::get_line_readonly
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "line"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the index of a line, which must be between 0 and\n  `pango_layout_get_line_count(layout) - 1`, inclusive."
--                 , 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_get_line_readonly" pango_layout_get_line_readonly :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- line : TBasicType TInt
    IO (Ptr Pango.LayoutLine.LayoutLine)

-- | Retrieves a particular line from a @PangoLayout@.
-- 
-- This is a faster alternative to 'GI.Pango.Objects.Layout.layoutGetLine',
-- but the user is not expected to modify the contents of the line
-- (glyphs, glyph widths, etc.).
-- 
-- /Since: 1.16/
layoutGetLineReadonly ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@line@/: the index of a line, which must be between 0 and
    --   @pango_layout_get_line_count(layout) - 1@, inclusive.
    -> m (Maybe Pango.LayoutLine.LayoutLine)
    -- ^ __Returns:__ the requested @PangoLayoutLine@,
    --   or 'P.Nothing' if the index is out of range. This layout line can be ref\'ed
    --   and retained, but will become invalid if changes are made to the
    --   @PangoLayout@. No changes should be made to the line.
layoutGetLineReadonly :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m (Maybe LayoutLine)
layoutGetLineReadonly a
layout Int32
line = IO (Maybe LayoutLine) -> m (Maybe LayoutLine)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe LayoutLine) -> m (Maybe LayoutLine))
-> IO (Maybe LayoutLine) -> m (Maybe LayoutLine)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr LayoutLine
result <- Ptr Layout -> Int32 -> IO (Ptr LayoutLine)
pango_layout_get_line_readonly Ptr Layout
layout' Int32
line
    Maybe LayoutLine
maybeResult <- Ptr LayoutLine
-> (Ptr LayoutLine -> IO LayoutLine) -> IO (Maybe LayoutLine)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr LayoutLine
result ((Ptr LayoutLine -> IO LayoutLine) -> IO (Maybe LayoutLine))
-> (Ptr LayoutLine -> IO LayoutLine) -> IO (Maybe LayoutLine)
forall a b. (a -> b) -> a -> b
$ \Ptr LayoutLine
result' -> do
        LayoutLine
result'' <- ((ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr LayoutLine -> LayoutLine
Pango.LayoutLine.LayoutLine) Ptr LayoutLine
result'
        LayoutLine -> IO LayoutLine
forall (m :: * -> *) a. Monad m => a -> m a
return LayoutLine
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Maybe LayoutLine -> IO (Maybe LayoutLine)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LayoutLine
maybeResult

#if defined(ENABLE_OVERLOADING)
data LayoutGetLineReadonlyMethodInfo
instance (signature ~ (Int32 -> m (Maybe Pango.LayoutLine.LayoutLine)), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetLineReadonlyMethodInfo a signature where
    overloadedMethod = layoutGetLineReadonly

instance O.OverloadedMethodInfo LayoutGetLineReadonlyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetLineReadonly",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetLineReadonly"
        })


#endif

-- method Layout::get_line_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TFloat)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_line_spacing" pango_layout_get_line_spacing :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CFloat

-- | Gets the line spacing factor of /@layout@/.
-- 
-- See 'GI.Pango.Objects.Layout.layoutSetLineSpacing'.
-- 
-- /Since: 1.44/
layoutGetLineSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Float
layoutGetLineSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Float
layoutGetLineSpacing a
layout = IO Float -> m Float
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Float -> m Float) -> IO Float -> m Float
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CFloat
result <- Ptr Layout -> IO CFloat
pango_layout_get_line_spacing Ptr Layout
layout'
    let result' :: Float
result' = CFloat -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac CFloat
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Float -> IO Float
forall (m :: * -> *) a. Monad m => a -> m a
return Float
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetLineSpacingMethodInfo
instance (signature ~ (m Float), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetLineSpacingMethodInfo a signature where
    overloadedMethod = layoutGetLineSpacing

instance O.OverloadedMethodInfo LayoutGetLineSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetLineSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetLineSpacing"
        })


#endif

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

foreign import ccall "pango_layout_get_lines" pango_layout_get_lines :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO (Ptr (GSList (Ptr Pango.LayoutLine.LayoutLine)))

-- | Returns the lines of the /@layout@/ as a list.
-- 
-- Use the faster 'GI.Pango.Objects.Layout.layoutGetLinesReadonly' if you do not
-- plan to modify the contents of the lines (glyphs, glyph widths, etc.).
layoutGetLines ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m [Pango.LayoutLine.LayoutLine]
    -- ^ __Returns:__ a @GSList@
    --   containing the lines in the layout. This points to internal data of the
    --   @PangoLayout@ and must be used with care. It will become invalid on any
    --   change to the layout\'s text or properties.
layoutGetLines :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m [LayoutLine]
layoutGetLines a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr (GSList (Ptr LayoutLine))
result <- Ptr Layout -> IO (Ptr (GSList (Ptr LayoutLine)))
pango_layout_get_lines Ptr Layout
layout'
    [Ptr LayoutLine]
result' <- Ptr (GSList (Ptr LayoutLine)) -> IO [Ptr LayoutLine]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr LayoutLine))
result
    [LayoutLine]
result'' <- (Ptr LayoutLine -> IO LayoutLine)
-> [Ptr LayoutLine] -> IO [LayoutLine]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr LayoutLine -> LayoutLine
Pango.LayoutLine.LayoutLine) [Ptr LayoutLine]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    [LayoutLine] -> IO [LayoutLine]
forall (m :: * -> *) a. Monad m => a -> m a
return [LayoutLine]
result''

#if defined(ENABLE_OVERLOADING)
data LayoutGetLinesMethodInfo
instance (signature ~ (m [Pango.LayoutLine.LayoutLine]), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetLinesMethodInfo a signature where
    overloadedMethod = layoutGetLines

instance O.OverloadedMethodInfo LayoutGetLinesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetLines",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetLines"
        })


#endif

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

foreign import ccall "pango_layout_get_lines_readonly" pango_layout_get_lines_readonly :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO (Ptr (GSList (Ptr Pango.LayoutLine.LayoutLine)))

-- | Returns the lines of the /@layout@/ as a list.
-- 
-- This is a faster alternative to 'GI.Pango.Objects.Layout.layoutGetLines',
-- but the user is not expected to modify the contents of the lines
-- (glyphs, glyph widths, etc.).
-- 
-- /Since: 1.16/
layoutGetLinesReadonly ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m [Pango.LayoutLine.LayoutLine]
    -- ^ __Returns:__ a @GSList@
    --   containing the lines in the layout. This points to internal data of the
    --   @PangoLayout@ and must be used with care. It will become invalid on any
    --   change to the layout\'s text or properties. No changes should be made to
    --   the lines.
layoutGetLinesReadonly :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m [LayoutLine]
layoutGetLinesReadonly a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr (GSList (Ptr LayoutLine))
result <- Ptr Layout -> IO (Ptr (GSList (Ptr LayoutLine)))
pango_layout_get_lines_readonly Ptr Layout
layout'
    [Ptr LayoutLine]
result' <- Ptr (GSList (Ptr LayoutLine)) -> IO [Ptr LayoutLine]
forall a. Ptr (GSList (Ptr a)) -> IO [Ptr a]
unpackGSList Ptr (GSList (Ptr LayoutLine))
result
    [LayoutLine]
result'' <- (Ptr LayoutLine -> IO LayoutLine)
-> [Ptr LayoutLine] -> IO [LayoutLine]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr LayoutLine -> LayoutLine)
-> Ptr LayoutLine -> IO LayoutLine
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr LayoutLine -> LayoutLine
Pango.LayoutLine.LayoutLine) [Ptr LayoutLine]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    [LayoutLine] -> IO [LayoutLine]
forall (m :: * -> *) a. Monad m => a -> m a
return [LayoutLine]
result''

#if defined(ENABLE_OVERLOADING)
data LayoutGetLinesReadonlyMethodInfo
instance (signature ~ (m [Pango.LayoutLine.LayoutLine]), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetLinesReadonlyMethodInfo a signature where
    overloadedMethod = layoutGetLinesReadonly

instance O.OverloadedMethodInfo LayoutGetLinesReadonlyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetLinesReadonly",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetLinesReadonly"
        })


#endif

-- method Layout::get_log_attrs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attrs"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Pango" , name = "LogAttr" })
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "\n  location to store a pointer to an array of logical attributes.\n  This value must be freed with g_free()."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferContainer
--           }
--       , Arg
--           { argCName = "n_attrs"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store the number of the attributes in the\n  array. (The stored value will be one more than the total number\n  of characters in the layout, since there need to be attributes\n  corresponding to both the position before the first character\n  and the position after the last character.)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_attrs"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just
--                          "location to store the number of the attributes in the\n  array. (The stored value will be one more than the total number\n  of characters in the layout, since there need to be attributes\n  corresponding to both the position before the first character\n  and the position after the last character.)"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_log_attrs" pango_layout_get_log_attrs :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Ptr (Ptr Pango.LogAttr.LogAttr) ->      -- attrs : TCArray False (-1) 2 (TInterface (Name {namespace = "Pango", name = "LogAttr"}))
    Ptr Int32 ->                            -- n_attrs : TBasicType TInt
    IO ()

-- | Retrieves an array of logical attributes for each character in
-- the /@layout@/.
layoutGetLogAttrs ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m ([Pango.LogAttr.LogAttr])
layoutGetLogAttrs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m [LogAttr]
layoutGetLogAttrs a
layout = IO [LogAttr] -> m [LogAttr]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [LogAttr] -> m [LogAttr]) -> IO [LogAttr] -> m [LogAttr]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr (Ptr LogAttr)
attrs <- IO (Ptr (Ptr LogAttr))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (Ptr Pango.LogAttr.LogAttr))
    Ptr Int32
nAttrs <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Layout -> Ptr (Ptr LogAttr) -> Ptr Int32 -> IO ()
pango_layout_get_log_attrs Ptr Layout
layout' Ptr (Ptr LogAttr)
attrs Ptr Int32
nAttrs
    Int32
nAttrs' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nAttrs
    Ptr LogAttr
attrs' <- Ptr (Ptr LogAttr) -> IO (Ptr LogAttr)
forall a. Storable a => Ptr a -> IO a
peek Ptr (Ptr LogAttr)
attrs
    [Ptr LogAttr]
attrs'' <- (Int -> Int32 -> Ptr LogAttr -> IO [Ptr LogAttr]
forall a b. Integral a => Int -> a -> Ptr b -> IO [Ptr b]
unpackBlockArrayWithLength Int
64 Int32
nAttrs') Ptr LogAttr
attrs'
    [LogAttr]
attrs''' <- (Ptr LogAttr -> IO LogAttr) -> [Ptr LogAttr] -> IO [LogAttr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr LogAttr -> LogAttr) -> Ptr LogAttr -> IO LogAttr
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr LogAttr -> LogAttr
Pango.LogAttr.LogAttr) [Ptr LogAttr]
attrs''
    Ptr LogAttr -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr LogAttr
attrs'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Ptr (Ptr LogAttr) -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr (Ptr LogAttr)
attrs
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nAttrs
    [LogAttr] -> IO [LogAttr]
forall (m :: * -> *) a. Monad m => a -> m a
return [LogAttr]
attrs'''

#if defined(ENABLE_OVERLOADING)
data LayoutGetLogAttrsMethodInfo
instance (signature ~ (m ([Pango.LogAttr.LogAttr])), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetLogAttrsMethodInfo a signature where
    overloadedMethod = layoutGetLogAttrs

instance O.OverloadedMethodInfo LayoutGetLogAttrsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetLogAttrs",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetLogAttrs"
        })


#endif

-- method Layout::get_log_attrs_readonly
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "n_attrs"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store the number of the attributes in\n  the array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "n_attrs"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just
--                          "location to store the number of the attributes in\n  the array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just
--               (TCArray
--                  False
--                  (-1)
--                  1
--                  (TInterface Name { namespace = "Pango" , name = "LogAttr" }))
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_log_attrs_readonly" pango_layout_get_log_attrs_readonly :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Ptr Int32 ->                            -- n_attrs : TBasicType TInt
    IO (Ptr Pango.LogAttr.LogAttr)

-- | Retrieves an array of logical attributes for each character in
-- the /@layout@/.
-- 
-- This is a faster alternative to 'GI.Pango.Objects.Layout.layoutGetLogAttrs'.
-- The returned array is part of /@layout@/ and must not be modified.
-- Modifying the layout will invalidate the returned array.
-- 
-- The number of attributes returned in /@nAttrs@/ will be one more
-- than the total number of characters in the layout, since there
-- need to be attributes corresponding to both the position before
-- the first character and the position after the last character.
-- 
-- /Since: 1.30/
layoutGetLogAttrsReadonly ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m [Pango.LogAttr.LogAttr]
    -- ^ __Returns:__ an array of logical attributes
layoutGetLogAttrsReadonly :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m [LogAttr]
layoutGetLogAttrsReadonly a
layout = IO [LogAttr] -> m [LogAttr]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [LogAttr] -> m [LogAttr]) -> IO [LogAttr] -> m [LogAttr]
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Int32
nAttrs <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr LogAttr
result <- Ptr Layout -> Ptr Int32 -> IO (Ptr LogAttr)
pango_layout_get_log_attrs_readonly Ptr Layout
layout' Ptr Int32
nAttrs
    Int32
nAttrs' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
nAttrs
    Text -> Ptr LogAttr -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"layoutGetLogAttrsReadonly" Ptr LogAttr
result
    [Ptr LogAttr]
result' <- (Int -> Int32 -> Ptr LogAttr -> IO [Ptr LogAttr]
forall a b. Integral a => Int -> a -> Ptr b -> IO [Ptr b]
unpackBlockArrayWithLength Int
64 Int32
nAttrs') Ptr LogAttr
result
    [LogAttr]
result'' <- (Ptr LogAttr -> IO LogAttr) -> [Ptr LogAttr] -> IO [LogAttr]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr LogAttr -> LogAttr) -> Ptr LogAttr -> IO LogAttr
forall a.
(HasCallStack, BoxedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newPtr ManagedPtr LogAttr -> LogAttr
Pango.LogAttr.LogAttr) [Ptr LogAttr]
result'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
nAttrs
    [LogAttr] -> IO [LogAttr]
forall (m :: * -> *) a. Monad m => a -> m a
return [LogAttr]
result''

#if defined(ENABLE_OVERLOADING)
data LayoutGetLogAttrsReadonlyMethodInfo
instance (signature ~ (m [Pango.LogAttr.LogAttr]), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetLogAttrsReadonlyMethodInfo a signature where
    overloadedMethod = layoutGetLogAttrsReadonly

instance O.OverloadedMethodInfo LayoutGetLogAttrsReadonlyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetLogAttrsReadonly",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetLogAttrsReadonly"
        })


#endif

-- method Layout::get_pixel_extents
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , 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 the\n  layout as drawn"
--                 , 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 layout"
--                 , 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_get_pixel_extents" pango_layout_get_pixel_extents :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    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 /@layout@/ in device units.
-- 
-- This function just calls 'GI.Pango.Objects.Layout.layoutGetExtents' followed by
-- two [func/@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').
layoutGetPixelExtents ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutGetPixelExtents :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m (Rectangle, Rectangle)
layoutGetPixelExtents a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    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 Layout -> Ptr Rectangle -> Ptr Rectangle -> IO ()
pango_layout_get_pixel_extents Ptr Layout
layout' 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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    (Rectangle, Rectangle) -> IO (Rectangle, Rectangle)
forall (m :: * -> *) a. Monad m => a -> m a
return (Rectangle
inkRect', Rectangle
logicalRect')

#if defined(ENABLE_OVERLOADING)
data LayoutGetPixelExtentsMethodInfo
instance (signature ~ (m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetPixelExtentsMethodInfo a signature where
    overloadedMethod = layoutGetPixelExtents

instance O.OverloadedMethodInfo LayoutGetPixelExtentsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetPixelExtents",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetPixelExtents"
        })


#endif

-- method Layout::get_pixel_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the logical width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the logical 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_get_pixel_size" pango_layout_get_pixel_size :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Ptr Int32 ->                            -- width : TBasicType TInt
    Ptr Int32 ->                            -- height : TBasicType TInt
    IO ()

-- | Determines the logical width and height of a @PangoLayout@ in device
-- units.
-- 
-- 'GI.Pango.Objects.Layout.layoutGetSize' returns the width and height
-- scaled by 'GI.Pango.Constants.SCALE'. This is simply a convenience function
-- around 'GI.Pango.Objects.Layout.layoutGetPixelExtents'.
layoutGetPixelSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m ((Int32, Int32))
layoutGetPixelSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m (Int32, Int32)
layoutGetPixelSize a
layout = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Layout -> Ptr Int32 -> Ptr Int32 -> IO ()
pango_layout_get_pixel_size Ptr Layout
layout' Ptr Int32
width Ptr Int32
height
    Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
width', Int32
height')

#if defined(ENABLE_OVERLOADING)
data LayoutGetPixelSizeMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetPixelSizeMethodInfo a signature where
    overloadedMethod = layoutGetPixelSize

instance O.OverloadedMethodInfo LayoutGetPixelSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetPixelSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetPixelSize"
        })


#endif

-- method Layout::get_serial
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_serial" pango_layout_get_serial :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO Word32

-- | Returns the current serial number of /@layout@/.
-- 
-- The serial number is initialized to an small number larger than zero
-- when a new layout is created and is increased whenever the layout is
-- changed using any of the setter functions, or the @PangoContext@ it
-- uses has changed. The serial may wrap, but will never have the value 0.
-- Since it can wrap, never compare it with \"less than\", always use \"not equals\".
-- 
-- This can be used to automatically detect changes to a @PangoLayout@,
-- and is useful for example to decide whether a layout needs redrawing.
-- To force the serial to be increased, use
-- 'GI.Pango.Objects.Layout.layoutContextChanged'.
-- 
-- /Since: 1.32.4/
layoutGetSerial ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Word32
    -- ^ __Returns:__ The current serial number of /@layout@/.
layoutGetSerial :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Word32
layoutGetSerial a
layout = 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
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Word32
result <- Ptr Layout -> IO Word32
pango_layout_get_serial Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Word32 -> IO Word32
forall (m :: * -> *) a. Monad m => a -> m a
return Word32
result

#if defined(ENABLE_OVERLOADING)
data LayoutGetSerialMethodInfo
instance (signature ~ (m Word32), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetSerialMethodInfo a signature where
    overloadedMethod = layoutGetSerial

instance O.OverloadedMethodInfo LayoutGetSerialMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetSerial",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetSerial"
        })


#endif

-- method Layout::get_single_paragraph_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_single_paragraph_mode" pango_layout_get_single_paragraph_mode :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CInt

-- | Obtains whether /@layout@/ is in single paragraph mode.
-- 
-- See 'GI.Pango.Objects.Layout.layoutSetSingleParagraphMode'.
layoutGetSingleParagraphMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the layout does not break paragraphs
    --   at paragraph separator characters, 'P.False' otherwise
layoutGetSingleParagraphMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Bool
layoutGetSingleParagraphMode a
layout = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr Layout -> IO CInt
pango_layout_get_single_paragraph_mode Ptr Layout
layout'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetSingleParagraphModeMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetSingleParagraphModeMethodInfo a signature where
    overloadedMethod = layoutGetSingleParagraphMode

instance O.OverloadedMethodInfo LayoutGetSingleParagraphModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetSingleParagraphMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetSingleParagraphMode"
        })


#endif

-- method Layout::get_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the logical width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "location to store the logical 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_get_size" pango_layout_get_size :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Ptr Int32 ->                            -- width : TBasicType TInt
    Ptr Int32 ->                            -- height : TBasicType TInt
    IO ()

-- | Determines the logical width and height of a @PangoLayout@ in Pango
-- units.
-- 
-- This is simply a convenience function around 'GI.Pango.Objects.Layout.layoutGetExtents'.
layoutGetSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m ((Int32, Int32))
layoutGetSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m (Int32, Int32)
layoutGetSize a
layout = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Int32
width <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
height <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Layout -> Ptr Int32 -> Ptr Int32 -> IO ()
pango_layout_get_size Ptr Layout
layout' Ptr Int32
width Ptr Int32
height
    Int32
width' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
width
    Int32
height' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
width
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
height
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
width', Int32
height')

#if defined(ENABLE_OVERLOADING)
data LayoutGetSizeMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetSizeMethodInfo a signature where
    overloadedMethod = layoutGetSize

instance O.OverloadedMethodInfo LayoutGetSizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetSize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetSize"
        })


#endif

-- method Layout::get_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_spacing" pango_layout_get_spacing :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO Int32

-- | Gets the amount of spacing between the lines of the layout.
layoutGetSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Int32
    -- ^ __Returns:__ the spacing in Pango units
layoutGetSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Int32
layoutGetSpacing a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr Layout -> IO Int32
pango_layout_get_spacing Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data LayoutGetSpacingMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetSpacingMethodInfo a signature where
    overloadedMethod = layoutGetSpacing

instance O.OverloadedMethodInfo LayoutGetSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetSpacing"
        })


#endif

-- method Layout::get_tabs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "TabArray" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_tabs" pango_layout_get_tabs :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO (Ptr Pango.TabArray.TabArray)

-- | Gets the current @PangoTabArray@ used by this layout.
-- 
-- If no @PangoTabArray@ has been set, then the default tabs are
-- in use and 'P.Nothing' is returned. Default tabs are every 8 spaces.
-- 
-- The return value should be freed with 'GI.Pango.Structs.TabArray.tabArrayFree'.
layoutGetTabs ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m (Maybe Pango.TabArray.TabArray)
    -- ^ __Returns:__ a copy of the tabs for this layout
layoutGetTabs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m (Maybe TabArray)
layoutGetTabs a
layout = IO (Maybe TabArray) -> m (Maybe TabArray)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe TabArray) -> m (Maybe TabArray))
-> IO (Maybe TabArray) -> m (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr TabArray
result <- Ptr Layout -> IO (Ptr TabArray)
pango_layout_get_tabs Ptr Layout
layout'
    Maybe TabArray
maybeResult <- Ptr TabArray
-> (Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr TabArray
result ((Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray))
-> (Ptr TabArray -> IO TabArray) -> IO (Maybe TabArray)
forall a b. (a -> b) -> a -> b
$ \Ptr TabArray
result' -> do
        TabArray
result'' <- ((ManagedPtr TabArray -> TabArray) -> Ptr TabArray -> IO TabArray
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr TabArray -> TabArray
Pango.TabArray.TabArray) Ptr TabArray
result'
        TabArray -> IO TabArray
forall (m :: * -> *) a. Monad m => a -> m a
return TabArray
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Maybe TabArray -> IO (Maybe TabArray)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe TabArray
maybeResult

#if defined(ENABLE_OVERLOADING)
data LayoutGetTabsMethodInfo
instance (signature ~ (m (Maybe Pango.TabArray.TabArray)), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetTabsMethodInfo a signature where
    overloadedMethod = layoutGetTabs

instance O.OverloadedMethodInfo LayoutGetTabsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetTabs",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetTabs"
        })


#endif

-- method Layout::get_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_text" pango_layout_get_text :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CString

-- | Gets the text in the layout.
-- 
-- The returned text should not be freed or modified.
layoutGetText ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m T.Text
    -- ^ __Returns:__ the text in the /@layout@/
layoutGetText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Text
layoutGetText a
layout = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CString
result <- Ptr Layout -> IO CString
pango_layout_get_text Ptr Layout
layout'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"layoutGetText" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetTextMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetTextMethodInfo a signature where
    overloadedMethod = layoutGetText

instance O.OverloadedMethodInfo LayoutGetTextMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetText",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetText"
        })


#endif

-- method Layout::get_unknown_glyphs_count
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_unknown_glyphs_count" pango_layout_get_unknown_glyphs_count :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO Int32

-- | Counts the number of unknown glyphs in /@layout@/.
-- 
-- This function can be used to determine if there are any fonts
-- available to render all characters in a certain string, or when
-- used in combination with 'GI.Pango.Enums.AttrTypeFallback', to check if a
-- certain font supports all the characters in the string.
-- 
-- /Since: 1.16/
layoutGetUnknownGlyphsCount ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Int32
    -- ^ __Returns:__ The number of unknown glyphs in /@layout@/
layoutGetUnknownGlyphsCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Int32
layoutGetUnknownGlyphsCount a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr Layout -> IO Int32
pango_layout_get_unknown_glyphs_count Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data LayoutGetUnknownGlyphsCountMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetUnknownGlyphsCountMethodInfo a signature where
    overloadedMethod = layoutGetUnknownGlyphsCount

instance O.OverloadedMethodInfo LayoutGetUnknownGlyphsCountMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetUnknownGlyphsCount",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetUnknownGlyphsCount"
        })


#endif

-- method Layout::get_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_width" pango_layout_get_width :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO Int32

-- | Gets the width to which the lines of the @PangoLayout@ should wrap.
layoutGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Int32
    -- ^ __Returns:__ the width in Pango units, or -1 if no width set.
layoutGetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Int32
layoutGetWidth a
layout = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Int32
result <- Ptr Layout -> IO Int32
pango_layout_get_width Ptr Layout
layout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data LayoutGetWidthMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetWidthMethodInfo a signature where
    overloadedMethod = layoutGetWidth

instance O.OverloadedMethodInfo LayoutGetWidthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetWidth"
        })


#endif

-- method Layout::get_wrap
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "WrapMode" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_get_wrap" pango_layout_get_wrap :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CUInt

-- | Gets the wrap mode for the layout.
-- 
-- Use 'GI.Pango.Objects.Layout.layoutIsWrapped' to query whether
-- any paragraphs were actually wrapped.
layoutGetWrap ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Pango.Enums.WrapMode
    -- ^ __Returns:__ active wrap mode.
layoutGetWrap :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m WrapMode
layoutGetWrap a
layout = IO WrapMode -> m WrapMode
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO WrapMode -> m WrapMode) -> IO WrapMode -> m WrapMode
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CUInt
result <- Ptr Layout -> IO CUInt
pango_layout_get_wrap Ptr Layout
layout'
    let result' :: WrapMode
result' = (Int -> WrapMode
forall a. Enum a => Int -> a
toEnum (Int -> WrapMode) -> (CUInt -> Int) -> CUInt -> WrapMode
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    WrapMode -> IO WrapMode
forall (m :: * -> *) a. Monad m => a -> m a
return WrapMode
result'

#if defined(ENABLE_OVERLOADING)
data LayoutGetWrapMethodInfo
instance (signature ~ (m Pango.Enums.WrapMode), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutGetWrapMethodInfo a signature where
    overloadedMethod = layoutGetWrap

instance O.OverloadedMethodInfo LayoutGetWrapMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutGetWrap",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutGetWrap"
        })


#endif

-- method Layout::index_to_line_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , 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 "the byte index 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 the\n  position of. If > 0, the trailing edge of the grapheme, if 0,\n  the leading of the grapheme"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "line"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store resulting line index. (which will\n  between 0 and pango_layout_get_line_count(layout) - 1)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "x_pos"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store resulting position within line\n  (%PANGO_SCALE units per device 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_index_to_line_x" pango_layout_index_to_line_x :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- index_ : TBasicType TInt
    CInt ->                                 -- trailing : TBasicType TBoolean
    Ptr Int32 ->                            -- line : TBasicType TInt
    Ptr Int32 ->                            -- x_pos : TBasicType TInt
    IO ()

-- | Converts from byte /@index_@/ within the /@layout@/ to line and X position.
-- 
-- The X position is measured from the left edge of the line.
layoutIndexToLineX ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@index_@/: the byte index 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, Int32))
layoutIndexToLineX :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> Bool -> m (Int32, Int32)
layoutIndexToLineX a
layout Int32
index_ Bool
trailing = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    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
line <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
xPos <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Layout -> Int32 -> CInt -> Ptr Int32 -> Ptr Int32 -> IO ()
pango_layout_index_to_line_x Ptr Layout
layout' Int32
index_ CInt
trailing' Ptr Int32
line Ptr Int32
xPos
    Int32
line' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
line
    Int32
xPos' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
xPos
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
line
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
xPos
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
line', Int32
xPos')

#if defined(ENABLE_OVERLOADING)
data LayoutIndexToLineXMethodInfo
instance (signature ~ (Int32 -> Bool -> m ((Int32, Int32))), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutIndexToLineXMethodInfo a signature where
    overloadedMethod = layoutIndexToLineX

instance O.OverloadedMethodInfo LayoutIndexToLineXMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutIndexToLineX",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutIndexToLineX"
        })


#endif

-- method Layout::index_to_pos
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , 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 index within @layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pos"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Rectangle" }
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "rectangle in which to store the position of the grapheme"
--                 , 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_index_to_pos" pango_layout_index_to_pos :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- index_ : TBasicType TInt
    Ptr Pango.Rectangle.Rectangle ->        -- pos : TInterface (Name {namespace = "Pango", name = "Rectangle"})
    IO ()

-- | Converts from an index within a @PangoLayout@ to the onscreen position
-- corresponding to the grapheme at that index.
-- 
-- The return value is represented as rectangle. Note that @pos->x@ is
-- always the leading edge of the grapheme and @pos->x + pos->width@ the
-- trailing edge of the grapheme. If the directionality of the grapheme
-- is right-to-left, then @pos->width@ will be negative.
layoutIndexToPos ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@index_@/: byte index within /@layout@/
    -> m (Pango.Rectangle.Rectangle)
layoutIndexToPos :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m Rectangle
layoutIndexToPos a
layout Int32
index_ = IO Rectangle -> m Rectangle
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Rectangle -> m Rectangle) -> IO Rectangle -> m Rectangle
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Rectangle
pos <- Int -> IO (Ptr Rectangle)
forall a. Int -> IO (Ptr a)
SP.callocBytes Int
16 :: IO (Ptr Pango.Rectangle.Rectangle)
    Ptr Layout -> Int32 -> Ptr Rectangle -> IO ()
pango_layout_index_to_pos Ptr Layout
layout' Int32
index_ Ptr Rectangle
pos
    Rectangle
pos' <- ((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
pos
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Rectangle -> IO Rectangle
forall (m :: * -> *) a. Monad m => a -> m a
return Rectangle
pos'

#if defined(ENABLE_OVERLOADING)
data LayoutIndexToPosMethodInfo
instance (signature ~ (Int32 -> m (Pango.Rectangle.Rectangle)), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutIndexToPosMethodInfo a signature where
    overloadedMethod = layoutIndexToPos

instance O.OverloadedMethodInfo LayoutIndexToPosMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutIndexToPos",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutIndexToPos"
        })


#endif

-- method Layout::is_ellipsized
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_is_ellipsized" pango_layout_is_ellipsized :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CInt

-- | Queries whether the layout had to ellipsize any paragraphs.
-- 
-- This returns 'P.True' if the ellipsization mode for /@layout@/
-- is not 'GI.Pango.Enums.EllipsizeModeNone', a positive width is set on /@layout@/,
-- and there are paragraphs exceeding that width that have to be
-- ellipsized.
-- 
-- /Since: 1.16/
layoutIsEllipsized ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if any paragraphs had to be ellipsized,
    --   'P.False' otherwise
layoutIsEllipsized :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Bool
layoutIsEllipsized a
layout = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr Layout -> IO CInt
pango_layout_is_ellipsized Ptr Layout
layout'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data LayoutIsEllipsizedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutIsEllipsizedMethodInfo a signature where
    overloadedMethod = layoutIsEllipsized

instance O.OverloadedMethodInfo LayoutIsEllipsizedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutIsEllipsized",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutIsEllipsized"
        })


#endif

-- method Layout::is_wrapped
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_is_wrapped" pango_layout_is_wrapped :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    IO CInt

-- | Queries whether the layout had to wrap any paragraphs.
-- 
-- This returns 'P.True' if a positive width is set on /@layout@/,
-- ellipsization mode of /@layout@/ is set to 'GI.Pango.Enums.EllipsizeModeNone',
-- and there are paragraphs exceeding the layout width that have
-- to be wrapped.
-- 
-- /Since: 1.16/
layoutIsWrapped ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if any paragraphs had to be wrapped, 'P.False'
    --   otherwise
layoutIsWrapped :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> m Bool
layoutIsWrapped a
layout = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CInt
result <- Ptr Layout -> IO CInt
pango_layout_is_wrapped Ptr Layout
layout'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data LayoutIsWrappedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutIsWrappedMethodInfo a signature where
    overloadedMethod = layoutIsWrapped

instance O.OverloadedMethodInfo LayoutIsWrappedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutIsWrapped",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutIsWrapped"
        })


#endif

-- method Layout::move_cursor_visually
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "strong"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "whether the moving cursor is the strong cursor or the\n  weak cursor. The strong cursor is the cursor corresponding\n  to text insertion in the base direction for the layout."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "old_index"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the byte index of the current cursor position"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "old_trailing"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "if 0, the cursor was at the leading edge of the\n  grapheme indicated by @old_index, if > 0, the cursor\n  was at the trailing edge."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "direction"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "direction to move cursor. A negative\n  value indicates motion to the left"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "new_index"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "location to store the new cursor byte index.\n  A value of -1 indicates that the cursor has been moved off the\n  beginning of the layout. A value of %G_MAXINT indicates that\n  the cursor has been moved off the end of the layout."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "new_trailing"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "number of characters to move forward from\n  the location returned for @new_index to get the position where\n  the cursor should be displayed. This allows distinguishing the\n  position at the beginning of one line from the position at the\n  end of the preceding line. @new_index is always on the line where\n  the cursor should be displayed."
--                 , 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_move_cursor_visually" pango_layout_move_cursor_visually :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CInt ->                                 -- strong : TBasicType TBoolean
    Int32 ->                                -- old_index : TBasicType TInt
    Int32 ->                                -- old_trailing : TBasicType TInt
    Int32 ->                                -- direction : TBasicType TInt
    Ptr Int32 ->                            -- new_index : TBasicType TInt
    Ptr Int32 ->                            -- new_trailing : TBasicType TInt
    IO ()

-- | Computes a new cursor position from an old position and a direction.
-- 
-- If /@direction@/ is positive, then the new position will cause the strong
-- or weak cursor to be displayed one position to right of where it was
-- with the old cursor position. If /@direction@/ is negative, it will be
-- moved to the left.
-- 
-- In the presence of bidirectional text, the correspondence between
-- logical and visual order will depend on the direction of the current
-- run, and there may be jumps when the cursor is moved off of the end
-- of a run.
-- 
-- Motion here is in cursor positions, not in characters, so a single
-- call to this function may move the cursor over multiple characters
-- when multiple characters combine to form a single grapheme.
layoutMoveCursorVisually ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Bool
    -- ^ /@strong@/: whether the moving cursor is the strong cursor or the
    --   weak cursor. The strong cursor is the cursor corresponding
    --   to text insertion in the base direction for the layout.
    -> Int32
    -- ^ /@oldIndex@/: the byte index of the current cursor position
    -> Int32
    -- ^ /@oldTrailing@/: if 0, the cursor was at the leading edge of the
    --   grapheme indicated by /@oldIndex@/, if > 0, the cursor
    --   was at the trailing edge.
    -> Int32
    -- ^ /@direction@/: direction to move cursor. A negative
    --   value indicates motion to the left
    -> m ((Int32, Int32))
layoutMoveCursorVisually :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Bool -> Int32 -> Int32 -> Int32 -> m (Int32, Int32)
layoutMoveCursorVisually a
layout Bool
strong Int32
oldIndex Int32
oldTrailing Int32
direction = IO (Int32, Int32) -> m (Int32, Int32)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let strong' :: CInt
strong' = (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
strong
    Ptr Int32
newIndex <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
newTrailing <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Layout
-> CInt
-> Int32
-> Int32
-> Int32
-> Ptr Int32
-> Ptr Int32
-> IO ()
pango_layout_move_cursor_visually Ptr Layout
layout' CInt
strong' Int32
oldIndex Int32
oldTrailing Int32
direction Ptr Int32
newIndex Ptr Int32
newTrailing
    Int32
newIndex' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
newIndex
    Int32
newTrailing' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
newTrailing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
newIndex
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
newTrailing
    (Int32, Int32) -> IO (Int32, Int32)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
newIndex', Int32
newTrailing')

#if defined(ENABLE_OVERLOADING)
data LayoutMoveCursorVisuallyMethodInfo
instance (signature ~ (Bool -> Int32 -> Int32 -> Int32 -> m ((Int32, Int32))), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutMoveCursorVisuallyMethodInfo a signature where
    overloadedMethod = layoutMoveCursorVisually

instance O.OverloadedMethodInfo LayoutMoveCursorVisuallyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutMoveCursorVisually",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutMoveCursorVisually"
        })


#endif

-- method Layout::serialize
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Pango" , name = "LayoutSerializeFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`PangoLayoutSerializeFlags`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "GLib" , name = "Bytes" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_layout_serialize" pango_layout_serialize :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Pango", name = "LayoutSerializeFlags"})
    IO (Ptr GLib.Bytes.Bytes)

-- | Serializes the /@layout@/ for later deserialization via [func/@pango@/.Layout.deserialize].
-- 
-- There are no guarantees about the format of the output across different
-- versions of Pango and [func/@pango@/.Layout.deserialize] will reject data
-- that it cannot parse.
-- 
-- The intended use of this function is testing, benchmarking and debugging.
-- The format is not meant as a permanent storage format.
-- 
-- /Since: 1.50/
layoutSerialize ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> [Pango.Flags.LayoutSerializeFlags]
    -- ^ /@flags@/: @PangoLayoutSerializeFlags@
    -> m GLib.Bytes.Bytes
    -- ^ __Returns:__ a @GBytes@ containing the serialized form of /@layout@/
layoutSerialize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> [LayoutSerializeFlags] -> m Bytes
layoutSerialize a
layout [LayoutSerializeFlags]
flags = IO Bytes -> m Bytes
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bytes -> m Bytes) -> IO Bytes -> m Bytes
forall a b. (a -> b) -> a -> b
$ do
    Ptr Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let flags' :: CUInt
flags' = [LayoutSerializeFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [LayoutSerializeFlags]
flags
    Ptr Bytes
result <- Ptr Layout -> CUInt -> IO (Ptr Bytes)
pango_layout_serialize Ptr Layout
layout' CUInt
flags'
    Text -> Ptr Bytes -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"layoutSerialize" Ptr Bytes
result
    Bytes
result' <- ((ManagedPtr Bytes -> Bytes) -> Ptr Bytes -> IO Bytes
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr Bytes -> Bytes
GLib.Bytes.Bytes) Ptr Bytes
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Bytes -> IO Bytes
forall (m :: * -> *) a. Monad m => a -> m a
return Bytes
result'

#if defined(ENABLE_OVERLOADING)
data LayoutSerializeMethodInfo
instance (signature ~ ([Pango.Flags.LayoutSerializeFlags] -> m GLib.Bytes.Bytes), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSerializeMethodInfo a signature where
    overloadedMethod = layoutSerialize

instance O.OverloadedMethodInfo LayoutSerializeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSerialize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSerialize"
        })


#endif

-- method Layout::set_alignment
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "alignment"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Alignment" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the alignment" , 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_set_alignment" pango_layout_set_alignment :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CUInt ->                                -- alignment : TInterface (Name {namespace = "Pango", name = "Alignment"})
    IO ()

-- | Sets the alignment for the layout: how partial lines are
-- positioned within the horizontal space available.
-- 
-- The default alignment is 'GI.Pango.Enums.AlignmentLeft'.
layoutSetAlignment ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Pango.Enums.Alignment
    -- ^ /@alignment@/: the alignment
    -> m ()
layoutSetAlignment :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Alignment -> m ()
layoutSetAlignment a
layout Alignment
alignment = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let alignment' :: CUInt
alignment' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Alignment -> Int) -> Alignment -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Alignment -> Int
forall a. Enum a => a -> Int
fromEnum) Alignment
alignment
    Ptr Layout -> CUInt -> IO ()
pango_layout_set_alignment Ptr Layout
layout' CUInt
alignment'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetAlignmentMethodInfo
instance (signature ~ (Pango.Enums.Alignment -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetAlignmentMethodInfo a signature where
    overloadedMethod = layoutSetAlignment

instance O.OverloadedMethodInfo LayoutSetAlignmentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetAlignment",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetAlignment"
        })


#endif

-- method Layout::set_attributes
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "attrs"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "AttrList" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoAttrList`" , 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_set_attributes" pango_layout_set_attributes :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Ptr Pango.AttrList.AttrList ->          -- attrs : TInterface (Name {namespace = "Pango", name = "AttrList"})
    IO ()

-- | Sets the text attributes for a layout object.
-- 
-- References /@attrs@/, so the caller can unref its reference.
layoutSetAttributes ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Maybe (Pango.AttrList.AttrList)
    -- ^ /@attrs@/: a @PangoAttrList@
    -> m ()
layoutSetAttributes :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Maybe AttrList -> m ()
layoutSetAttributes a
layout Maybe AttrList
attrs = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr AttrList
maybeAttrs <- case Maybe AttrList
attrs of
        Maybe AttrList
Nothing -> Ptr AttrList -> IO (Ptr AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AttrList
forall a. Ptr a
nullPtr
        Just AttrList
jAttrs -> do
            Ptr AttrList
jAttrs' <- AttrList -> IO (Ptr AttrList)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr AttrList
jAttrs
            Ptr AttrList -> IO (Ptr AttrList)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr AttrList
jAttrs'
    Ptr Layout -> Ptr AttrList -> IO ()
pango_layout_set_attributes Ptr Layout
layout' Ptr AttrList
maybeAttrs
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Maybe AttrList -> (AttrList -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe AttrList
attrs AttrList -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetAttributesMethodInfo
instance (signature ~ (Maybe (Pango.AttrList.AttrList) -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetAttributesMethodInfo a signature where
    overloadedMethod = layoutSetAttributes

instance O.OverloadedMethodInfo LayoutSetAttributesMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetAttributes",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetAttributes"
        })


#endif

-- method Layout::set_auto_dir
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "auto_dir"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "if %TRUE, compute the bidirectional base direction\n  from the layout's contents"
--                 , 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_set_auto_dir" pango_layout_set_auto_dir :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CInt ->                                 -- auto_dir : TBasicType TBoolean
    IO ()

-- | Sets whether to calculate the base direction
-- for the layout according to its contents.
-- 
-- When this flag is on (the default), then paragraphs in /@layout@/ that
-- begin with strong right-to-left characters (Arabic and Hebrew principally),
-- will have right-to-left layout, paragraphs with letters from other scripts
-- will have left-to-right layout. Paragraphs with only neutral characters
-- get their direction from the surrounding paragraphs.
-- 
-- When 'P.False', the choice between left-to-right and right-to-left
-- layout is done according to the base direction of the layout\'s
-- @PangoContext@. (See 'GI.Pango.Objects.Context.contextSetBaseDir').
-- 
-- When the auto-computed direction of a paragraph differs from the
-- base direction of the context, the interpretation of
-- 'GI.Pango.Enums.AlignmentLeft' and 'GI.Pango.Enums.AlignmentRight' are swapped.
-- 
-- /Since: 1.4/
layoutSetAutoDir ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Bool
    -- ^ /@autoDir@/: if 'P.True', compute the bidirectional base direction
    --   from the layout\'s contents
    -> m ()
layoutSetAutoDir :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Bool -> m ()
layoutSetAutoDir a
layout Bool
autoDir = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let autoDir' :: CInt
autoDir' = (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
autoDir
    Ptr Layout -> CInt -> IO ()
pango_layout_set_auto_dir Ptr Layout
layout' CInt
autoDir'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetAutoDirMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetAutoDirMethodInfo a signature where
    overloadedMethod = layoutSetAutoDir

instance O.OverloadedMethodInfo LayoutSetAutoDirMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetAutoDir",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetAutoDir"
        })


#endif

-- method Layout::set_ellipsize
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "ellipsize"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "EllipsizeMode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new ellipsization mode for @layout"
--                 , 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_set_ellipsize" pango_layout_set_ellipsize :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CUInt ->                                -- ellipsize : TInterface (Name {namespace = "Pango", name = "EllipsizeMode"})
    IO ()

-- | Sets the type of ellipsization being performed for /@layout@/.
-- 
-- Depending on the ellipsization mode /@ellipsize@/ text is
-- removed from the start, middle, or end of text so they
-- fit within the width and height of layout set with
-- 'GI.Pango.Objects.Layout.layoutSetWidth' and 'GI.Pango.Objects.Layout.layoutSetHeight'.
-- 
-- If the layout contains characters such as newlines that
-- force it to be layed out in multiple paragraphs, then whether
-- each paragraph is ellipsized separately or the entire layout
-- is ellipsized as a whole depends on the set height of the layout.
-- 
-- The default value is 'GI.Pango.Enums.EllipsizeModeNone'.
-- 
-- See 'GI.Pango.Objects.Layout.layoutSetHeight' for details.
-- 
-- /Since: 1.6/
layoutSetEllipsize ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Pango.Enums.EllipsizeMode
    -- ^ /@ellipsize@/: the new ellipsization mode for /@layout@/
    -> m ()
layoutSetEllipsize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> EllipsizeMode -> m ()
layoutSetEllipsize a
layout EllipsizeMode
ellipsize = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let ellipsize' :: CUInt
ellipsize' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (EllipsizeMode -> Int) -> EllipsizeMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. EllipsizeMode -> Int
forall a. Enum a => a -> Int
fromEnum) EllipsizeMode
ellipsize
    Ptr Layout -> CUInt -> IO ()
pango_layout_set_ellipsize Ptr Layout
layout' CUInt
ellipsize'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetEllipsizeMethodInfo
instance (signature ~ (Pango.Enums.EllipsizeMode -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetEllipsizeMethodInfo a signature where
    overloadedMethod = layoutSetEllipsize

instance O.OverloadedMethodInfo LayoutSetEllipsizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetEllipsize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetEllipsize"
        })


#endif

-- method Layout::set_font_description
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "desc"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "FontDescription" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the new `PangoFontDescription`\n  to unset the current font description"
--                 , 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_set_font_description" pango_layout_set_font_description :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Ptr Pango.FontDescription.FontDescription -> -- desc : TInterface (Name {namespace = "Pango", name = "FontDescription"})
    IO ()

-- | Sets the default font description for the layout.
-- 
-- If no font description is set on the layout, the
-- font description from the layout\'s context is used.
layoutSetFontDescription ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Maybe (Pango.FontDescription.FontDescription)
    -- ^ /@desc@/: the new @PangoFontDescription@
    --   to unset the current font description
    -> m ()
layoutSetFontDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Maybe FontDescription -> m ()
layoutSetFontDescription a
layout Maybe FontDescription
desc = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr FontDescription
maybeDesc <- case Maybe FontDescription
desc of
        Maybe FontDescription
Nothing -> Ptr FontDescription -> IO (Ptr FontDescription)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FontDescription
forall a. Ptr a
nullPtr
        Just FontDescription
jDesc -> do
            Ptr FontDescription
jDesc' <- FontDescription -> IO (Ptr FontDescription)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr FontDescription
jDesc
            Ptr FontDescription -> IO (Ptr FontDescription)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr FontDescription
jDesc'
    Ptr Layout -> Ptr FontDescription -> IO ()
pango_layout_set_font_description Ptr Layout
layout' Ptr FontDescription
maybeDesc
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Maybe FontDescription -> (FontDescription -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe FontDescription
desc FontDescription -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetFontDescriptionMethodInfo
instance (signature ~ (Maybe (Pango.FontDescription.FontDescription) -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetFontDescriptionMethodInfo a signature where
    overloadedMethod = layoutSetFontDescription

instance O.OverloadedMethodInfo LayoutSetFontDescriptionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetFontDescription",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetFontDescription"
        })


#endif

-- method Layout::set_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the desired height of the layout in Pango units if positive,\n  or desired number of lines if negative."
--                 , 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_set_height" pango_layout_set_height :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Sets the height to which the @PangoLayout@ should be ellipsized at.
-- 
-- There are two different behaviors, based on whether /@height@/ is positive
-- or negative.
-- 
-- If /@height@/ is positive, it will be the maximum height of the layout. Only
-- lines would be shown that would fit, and if there is any text omitted,
-- an ellipsis added. At least one line is included in each paragraph regardless
-- of how small the height value is. A value of zero will render exactly one
-- line for the entire layout.
-- 
-- If /@height@/ is negative, it will be the (negative of) maximum number of lines
-- per paragraph. That is, the total number of lines shown may well be more than
-- this value if the layout contains multiple paragraphs of text.
-- The default value of -1 means that the first line of each paragraph is ellipsized.
-- This behavior may be changed in the future to act per layout instead of per
-- paragraph. File a bug against pango at
-- <https://gitlab.gnome.org/gnome/pango https://gitlab.gnome.org/gnome/pango>
-- if your code relies on this behavior.
-- 
-- Height setting only has effect if a positive width is set on
-- /@layout@/ and ellipsization mode of /@layout@/ is not 'GI.Pango.Enums.EllipsizeModeNone'.
-- The behavior is undefined if a height other than -1 is set and
-- ellipsization mode is set to 'GI.Pango.Enums.EllipsizeModeNone', and may change in the
-- future.
-- 
-- /Since: 1.20/
layoutSetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@.
    -> Int32
    -- ^ /@height@/: the desired height of the layout in Pango units if positive,
    --   or desired number of lines if negative.
    -> m ()
layoutSetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m ()
layoutSetHeight a
layout Int32
height = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Layout -> Int32 -> IO ()
pango_layout_set_height Ptr Layout
layout' Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetHeightMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetHeightMethodInfo a signature where
    overloadedMethod = layoutSetHeight

instance O.OverloadedMethodInfo LayoutSetHeightMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetHeight",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetHeight"
        })


#endif

-- method Layout::set_indent
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "indent"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the amount by which to indent"
--                 , 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_set_indent" pango_layout_set_indent :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- indent : TBasicType TInt
    IO ()

-- | Sets the width in Pango units to indent each paragraph.
-- 
-- A negative value of /@indent@/ will produce a hanging indentation.
-- That is, the first line will have the full width, and subsequent
-- lines will be indented by the absolute value of /@indent@/.
-- 
-- The indent setting is ignored if layout alignment is set to
-- 'GI.Pango.Enums.AlignmentCenter'.
-- 
-- The default value is 0.
layoutSetIndent ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@indent@/: the amount by which to indent
    -> m ()
layoutSetIndent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m ()
layoutSetIndent a
layout Int32
indent = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Layout -> Int32 -> IO ()
pango_layout_set_indent Ptr Layout
layout' Int32
indent
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetIndentMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetIndentMethodInfo a signature where
    overloadedMethod = layoutSetIndent

instance O.OverloadedMethodInfo LayoutSetIndentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetIndent",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetIndent"
        })


#endif

-- method Layout::set_justify
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "justify"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether the lines in the layout should be justified"
--                 , 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_set_justify" pango_layout_set_justify :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CInt ->                                 -- justify : TBasicType TBoolean
    IO ()

-- | Sets whether each complete line should be stretched to fill the
-- entire width of the layout.
-- 
-- Stretching is typically done by adding whitespace, but for some scripts
-- (such as Arabic), the justification may be done in more complex ways,
-- like extending the characters.
-- 
-- Note that this setting is not implemented and so is ignored in
-- Pango older than 1.18.
-- 
-- Note that tabs and justification conflict with each other:
-- Justification will move content away from its tab-aligned
-- positions.
-- 
-- The default value is 'P.False'.
-- 
-- Also see 'GI.Pango.Objects.Layout.layoutSetJustifyLastLine'.
layoutSetJustify ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Bool
    -- ^ /@justify@/: whether the lines in the layout should be justified
    -> m ()
layoutSetJustify :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Bool -> m ()
layoutSetJustify a
layout Bool
justify = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let justify' :: CInt
justify' = (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
justify
    Ptr Layout -> CInt -> IO ()
pango_layout_set_justify Ptr Layout
layout' CInt
justify'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetJustifyMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetJustifyMethodInfo a signature where
    overloadedMethod = layoutSetJustify

instance O.OverloadedMethodInfo LayoutSetJustifyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetJustify",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetJustify"
        })


#endif

-- method Layout::set_justify_last_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "justify"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether the last line in the layout should be justified"
--                 , 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_set_justify_last_line" pango_layout_set_justify_last_line :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CInt ->                                 -- justify : TBasicType TBoolean
    IO ()

-- | Sets whether the last line should be stretched to fill the
-- entire width of the layout.
-- 
-- This only has an effect if 'GI.Pango.Objects.Layout.layoutSetJustify' has
-- been called as well.
-- 
-- The default value is 'P.False'.
-- 
-- /Since: 1.50/
layoutSetJustifyLastLine ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Bool
    -- ^ /@justify@/: whether the last line in the layout should be justified
    -> m ()
layoutSetJustifyLastLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Bool -> m ()
layoutSetJustifyLastLine a
layout Bool
justify = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let justify' :: CInt
justify' = (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
justify
    Ptr Layout -> CInt -> IO ()
pango_layout_set_justify_last_line Ptr Layout
layout' CInt
justify'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetJustifyLastLineMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetJustifyLastLineMethodInfo a signature where
    overloadedMethod = layoutSetJustifyLastLine

instance O.OverloadedMethodInfo LayoutSetJustifyLastLineMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetJustifyLastLine",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetJustifyLastLine"
        })


#endif

-- method Layout::set_line_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "factor"
--           , argType = TBasicType TFloat
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new line spacing factor"
--                 , 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_set_line_spacing" pango_layout_set_line_spacing :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CFloat ->                               -- factor : TBasicType TFloat
    IO ()

-- | Sets a factor for line spacing.
-- 
-- Typical values are: 0, 1, 1.5, 2. The default values is 0.
-- 
-- If /@factor@/ is non-zero, lines are placed so that
-- 
--     baseline2 = baseline1 + factor * height2
-- 
-- where height2 is the line height of the second line
-- (as determined by the font(s)). In this case, the spacing
-- set with 'GI.Pango.Objects.Layout.layoutSetSpacing' is ignored.
-- 
-- If /@factor@/ is zero (the default), spacing is applied as before.
-- 
-- Note: for semantics that are closer to the CSS line-height
-- property, see 'GI.Pango.Functions.attrLineHeightNew'.
-- 
-- /Since: 1.44/
layoutSetLineSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Float
    -- ^ /@factor@/: the new line spacing factor
    -> m ()
layoutSetLineSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Float -> m ()
layoutSetLineSpacing a
layout Float
factor = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let factor' :: CFloat
factor' = Float -> CFloat
forall a b. (Real a, Fractional b) => a -> b
realToFrac Float
factor
    Ptr Layout -> CFloat -> IO ()
pango_layout_set_line_spacing Ptr Layout
layout' CFloat
factor'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetLineSpacingMethodInfo
instance (signature ~ (Float -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetLineSpacingMethodInfo a signature where
    overloadedMethod = layoutSetLineSpacing

instance O.OverloadedMethodInfo LayoutSetLineSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetLineSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetLineSpacing"
        })


#endif

-- method Layout::set_markup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "markup"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "marked-up text" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "length of marked-up text in bytes, or -1 if @markup is\n  `NUL`-terminated"
--                 , 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_set_markup" pango_layout_set_markup :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CString ->                              -- markup : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt
    IO ()

-- | Sets the layout text and attribute list from marked-up text.
-- 
-- See <http://developer.gnome.org/pango/stable/pango_markup.html Pango Markup>).
-- 
-- Replaces the current text and attribute list.
-- 
-- This is the same as 'GI.Pango.Objects.Layout.layoutSetMarkupWithAccel',
-- but the markup text isn\'t scanned for accelerators.
layoutSetMarkup ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> T.Text
    -- ^ /@markup@/: marked-up text
    -> Int32
    -- ^ /@length@/: length of marked-up text in bytes, or -1 if /@markup@/ is
    --   @NUL@-terminated
    -> m ()
layoutSetMarkup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Text -> Int32 -> m ()
layoutSetMarkup a
layout Text
markup Int32
length_ = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CString
markup' <- Text -> IO CString
textToCString Text
markup
    Ptr Layout -> CString -> Int32 -> IO ()
pango_layout_set_markup Ptr Layout
layout' CString
markup' Int32
length_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
markup'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetMarkupMethodInfo
instance (signature ~ (T.Text -> Int32 -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetMarkupMethodInfo a signature where
    overloadedMethod = layoutSetMarkup

instance O.OverloadedMethodInfo LayoutSetMarkupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetMarkup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetMarkup"
        })


#endif

-- XXX Could not generate method Layout::set_markup_with_accel
-- Not implemented: Don't know how to allocate "accel_char" of type TBasicType TUniChar
#if defined(ENABLE_OVERLOADING)
-- XXX: Dummy instance, since code generation failed.
-- Please file a bug at http://github.com/haskell-gi/haskell-gi.
data LayoutSetMarkupWithAccelMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "setMarkupWithAccel" Layout) => O.OverloadedMethod LayoutSetMarkupWithAccelMethodInfo o p where
    overloadedMethod = undefined

instance (o ~ O.UnsupportedMethodError "setMarkupWithAccel" Layout) => O.OverloadedMethodInfo LayoutSetMarkupWithAccelMethodInfo o where
    overloadedMethodInfo = undefined

#endif

-- method Layout::set_single_paragraph_mode
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setting"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "new setting" , 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_set_single_paragraph_mode" pango_layout_set_single_paragraph_mode :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CInt ->                                 -- setting : TBasicType TBoolean
    IO ()

-- | Sets the single paragraph mode of /@layout@/.
-- 
-- If /@setting@/ is 'P.True', do not treat newlines and similar characters
-- as paragraph separators; instead, keep all text in a single paragraph,
-- and display a glyph for paragraph separator characters. Used when
-- you want to allow editing of newlines on a single text line.
-- 
-- The default value is 'P.False'.
layoutSetSingleParagraphMode ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Bool
    -- ^ /@setting@/: new setting
    -> m ()
layoutSetSingleParagraphMode :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Bool -> m ()
layoutSetSingleParagraphMode a
layout Bool
setting = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let setting' :: CInt
setting' = (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
setting
    Ptr Layout -> CInt -> IO ()
pango_layout_set_single_paragraph_mode Ptr Layout
layout' CInt
setting'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetSingleParagraphModeMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetSingleParagraphModeMethodInfo a signature where
    overloadedMethod = layoutSetSingleParagraphMode

instance O.OverloadedMethodInfo LayoutSetSingleParagraphModeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetSingleParagraphMode",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetSingleParagraphMode"
        })


#endif

-- method Layout::set_spacing
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "spacing"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the amount of spacing"
--                 , 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_set_spacing" pango_layout_set_spacing :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- spacing : TBasicType TInt
    IO ()

-- | Sets the amount of spacing in Pango units between
-- the lines of the layout.
-- 
-- When placing lines with spacing, Pango arranges things so that
-- 
--     line2.top = line1.bottom + spacing
-- 
-- The default value is 0.
-- 
-- Note: Since 1.44, Pango is using the line height (as determined
-- by the font) for placing lines when the line spacing factor is set
-- to a non-zero value with 'GI.Pango.Objects.Layout.layoutSetLineSpacing'.
-- In that case, the /@spacing@/ set with this function is ignored.
-- 
-- Note: for semantics that are closer to the CSS line-height
-- property, see 'GI.Pango.Functions.attrLineHeightNew'.
layoutSetSpacing ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@spacing@/: the amount of spacing
    -> m ()
layoutSetSpacing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m ()
layoutSetSpacing a
layout Int32
spacing = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Layout -> Int32 -> IO ()
pango_layout_set_spacing Ptr Layout
layout' Int32
spacing
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetSpacingMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetSpacingMethodInfo a signature where
    overloadedMethod = layoutSetSpacing

instance O.OverloadedMethodInfo LayoutSetSpacingMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetSpacing",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetSpacing"
        })


#endif

-- method Layout::set_tabs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "tabs"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "TabArray" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoTabArray`" , 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_set_tabs" pango_layout_set_tabs :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Ptr Pango.TabArray.TabArray ->          -- tabs : TInterface (Name {namespace = "Pango", name = "TabArray"})
    IO ()

-- | Sets the tabs to use for /@layout@/, overriding the default tabs.
-- 
-- @PangoLayout@ will place content at the next tab position
-- whenever it meets a Tab character (U+0009).
-- 
-- By default, tabs are every 8 spaces. If /@tabs@/ is 'P.Nothing', the
-- default tabs are reinstated. /@tabs@/ is copied into the layout;
-- you must free your copy of /@tabs@/ yourself.
-- 
-- Note that tabs and justification conflict with each other:
-- Justification will move content away from its tab-aligned
-- positions. The same is true for alignments other than
-- 'GI.Pango.Enums.AlignmentLeft'.
layoutSetTabs ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Maybe (Pango.TabArray.TabArray)
    -- ^ /@tabs@/: a @PangoTabArray@
    -> m ()
layoutSetTabs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Maybe TabArray -> m ()
layoutSetTabs a
layout Maybe TabArray
tabs = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr TabArray
maybeTabs <- case Maybe TabArray
tabs of
        Maybe TabArray
Nothing -> Ptr TabArray -> IO (Ptr TabArray)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TabArray
forall a. Ptr a
nullPtr
        Just TabArray
jTabs -> do
            Ptr TabArray
jTabs' <- TabArray -> IO (Ptr TabArray)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr TabArray
jTabs
            Ptr TabArray -> IO (Ptr TabArray)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr TabArray
jTabs'
    Ptr Layout -> Ptr TabArray -> IO ()
pango_layout_set_tabs Ptr Layout
layout' Ptr TabArray
maybeTabs
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    Maybe TabArray -> (TabArray -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe TabArray
tabs TabArray -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetTabsMethodInfo
instance (signature ~ (Maybe (Pango.TabArray.TabArray) -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetTabsMethodInfo a signature where
    overloadedMethod = layoutSetTabs

instance O.OverloadedMethodInfo LayoutSetTabsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetTabs",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetTabs"
        })


#endif

-- method Layout::set_text
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the text" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "length"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "maximum length of @text, in bytes. -1 indicates that\n  the string is nul-terminated and the length should be calculated.\n  The text will also be truncated on encountering a nul-termination\n  even when @length is positive."
--                 , 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_set_text" pango_layout_set_text :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CString ->                              -- text : TBasicType TUTF8
    Int32 ->                                -- length : TBasicType TInt
    IO ()

-- | Sets the text of the layout.
-- 
-- This function validates /@text@/ and renders invalid UTF-8
-- with a placeholder glyph.
-- 
-- Note that if you have used 'GI.Pango.Objects.Layout.layoutSetMarkup' or
-- 'GI.Pango.Objects.Layout.layoutSetMarkupWithAccel' on /@layout@/ before, you
-- may want to call 'GI.Pango.Objects.Layout.layoutSetAttributes' to clear the
-- attributes set on the layout from the markup as this function does
-- not clear attributes.
layoutSetText ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> T.Text
    -- ^ /@text@/: the text
    -> Int32
    -- ^ /@length@/: maximum length of /@text@/, in bytes. -1 indicates that
    --   the string is nul-terminated and the length should be calculated.
    --   The text will also be truncated on encountering a nul-termination
    --   even when /@length@/ is positive.
    -> m ()
layoutSetText :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Text -> Int32 -> m ()
layoutSetText a
layout Text
text Int32
length_ = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    CString
text' <- Text -> IO CString
textToCString Text
text
    Ptr Layout -> CString -> Int32 -> IO ()
pango_layout_set_text Ptr Layout
layout' CString
text' Int32
length_
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
text'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetTextMethodInfo
instance (signature ~ (T.Text -> Int32 -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetTextMethodInfo a signature where
    overloadedMethod = layoutSetText

instance O.OverloadedMethodInfo LayoutSetTextMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetText",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetText"
        })


#endif

-- method Layout::set_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`." , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the desired width in Pango units, or -1 to indicate that no\n  wrapping or ellipsization should be performed."
--                 , 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_set_width" pango_layout_set_width :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- width : TBasicType TInt
    IO ()

-- | Sets the width to which the lines of the @PangoLayout@ should wrap or
-- ellipsized.
-- 
-- The default value is -1: no width set.
layoutSetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@.
    -> Int32
    -- ^ /@width@/: the desired width in Pango units, or -1 to indicate that no
    --   wrapping or ellipsization should be performed.
    -> m ()
layoutSetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> m ()
layoutSetWidth a
layout Int32
width = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    Ptr Layout -> Int32 -> IO ()
pango_layout_set_width Ptr Layout
layout' Int32
width
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetWidthMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetWidthMethodInfo a signature where
    overloadedMethod = layoutSetWidth

instance O.OverloadedMethodInfo LayoutSetWidthMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetWidth",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetWidth"
        })


#endif

-- method Layout::set_wrap
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "wrap"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "WrapMode" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the wrap mode" , 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_set_wrap" pango_layout_set_wrap :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CUInt ->                                -- wrap : TInterface (Name {namespace = "Pango", name = "WrapMode"})
    IO ()

-- | Sets the wrap mode.
-- 
-- The wrap mode only has effect if a width is set on the layout
-- with 'GI.Pango.Objects.Layout.layoutSetWidth'. To turn off wrapping,
-- set the width to -1.
-- 
-- The default value is 'GI.Pango.Enums.WrapModeWord'.
layoutSetWrap ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Pango.Enums.WrapMode
    -- ^ /@wrap@/: the wrap mode
    -> m ()
layoutSetWrap :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> WrapMode -> m ()
layoutSetWrap a
layout WrapMode
wrap = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let wrap' :: CUInt
wrap' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (WrapMode -> Int) -> WrapMode -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. WrapMode -> Int
forall a. Enum a => a -> Int
fromEnum) WrapMode
wrap
    Ptr Layout -> CUInt -> IO ()
pango_layout_set_wrap Ptr Layout
layout' CUInt
wrap'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data LayoutSetWrapMethodInfo
instance (signature ~ (Pango.Enums.WrapMode -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutSetWrapMethodInfo a signature where
    overloadedMethod = layoutSetWrap

instance O.OverloadedMethodInfo LayoutSetWrapMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutSetWrap",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutSetWrap"
        })


#endif

-- method Layout::write_to_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Pango" , name = "LayoutSerializeFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`PangoLayoutSerializeFlags`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "filename"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file to save it to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "pango_layout_write_to_file" pango_layout_write_to_file :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Pango", name = "LayoutSerializeFlags"})
    CString ->                              -- filename : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | A convenience method to serialize a layout to a file.
-- 
-- It is equivalent to calling 'GI.Pango.Objects.Layout.layoutSerialize'
-- followed by 'GI.GLib.Functions.fileSetContents'.
-- 
-- See those two functions for details on the arguments.
-- 
-- It is mostly intended for use inside a debugger to quickly dump
-- a layout to a file for later inspection.
-- 
-- /Since: 1.50/
layoutWriteToFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> [Pango.Flags.LayoutSerializeFlags]
    -- ^ /@flags@/: @PangoLayoutSerializeFlags@
    -> [Char]
    -- ^ /@filename@/: the file to save it to
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
layoutWriteToFile :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> [LayoutSerializeFlags] -> [Char] -> m ()
layoutWriteToFile a
layout [LayoutSerializeFlags]
flags [Char]
filename = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    let flags' :: CUInt
flags' = [LayoutSerializeFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [LayoutSerializeFlags]
flags
    CString
filename' <- [Char] -> IO CString
stringToCString [Char]
filename
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr Layout -> CUInt -> CString -> Ptr (Ptr GError) -> IO CInt
pango_layout_write_to_file Ptr Layout
layout' CUInt
flags' CString
filename'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
     )

#if defined(ENABLE_OVERLOADING)
data LayoutWriteToFileMethodInfo
instance (signature ~ ([Pango.Flags.LayoutSerializeFlags] -> [Char] -> m ()), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutWriteToFileMethodInfo a signature where
    overloadedMethod = layoutWriteToFile

instance O.OverloadedMethodInfo LayoutWriteToFileMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutWriteToFile",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutWriteToFile"
        })


#endif

-- method Layout::xy_to_index
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the X offset (in Pango units) from the left edge of the layout"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the Y offset (in Pango units) from the top edge of the layout"
--                 , 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"
--                 , 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 a integer indicating where\n  in the grapheme the user clicked. It will either be zero, or the\n  number of characters in the grapheme. 0 represents the leading edge\n  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_xy_to_index" pango_layout_xy_to_index :: 
    Ptr Layout ->                           -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    Ptr Int32 ->                            -- index_ : TBasicType TInt
    Ptr Int32 ->                            -- trailing : TBasicType TInt
    IO CInt

-- | Converts from X and Y position within a layout to the byte index to the
-- character at that logical position.
-- 
-- If the Y position is not inside the layout, the closest position is
-- chosen (the position will be clamped inside the layout). If the X position
-- is not within the layout, then the start or the end of the line is
-- chosen as described for 'GI.Pango.Structs.LayoutLine.layoutLineXToIndex'. If either
-- the X or Y positions were not inside the layout, then the function returns
-- 'P.False'; on an exact hit, it returns 'P.True'.
layoutXyToIndex ::
    (B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
    a
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@x@/: the X offset (in Pango units) from the left edge of the layout
    -> Int32
    -- ^ /@y@/: the Y offset (in Pango units) from the top edge of the layout
    -> m ((Bool, Int32, Int32))
    -- ^ __Returns:__ 'P.True' if the coordinates were inside text, 'P.False' otherwise
layoutXyToIndex :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsLayout a) =>
a -> Int32 -> Int32 -> m (Bool, Int32, Int32)
layoutXyToIndex a
layout Int32
x Int32
y = 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 Layout
layout' <- a -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
layout
    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 Layout -> Int32 -> Int32 -> Ptr Int32 -> Ptr Int32 -> IO CInt
pango_layout_xy_to_index Ptr Layout
layout' Int32
x Int32
y 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
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
    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 LayoutXyToIndexMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ((Bool, Int32, Int32))), MonadIO m, IsLayout a) => O.OverloadedMethod LayoutXyToIndexMethodInfo a signature where
    overloadedMethod = layoutXyToIndex

instance O.OverloadedMethodInfo LayoutXyToIndexMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Pango.Objects.Layout.layoutXyToIndex",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-pango-1.0.25/docs/GI-Pango-Objects-Layout.html#v:layoutXyToIndex"
        })


#endif

-- method Layout::deserialize
-- method type : MemberFunction
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Context" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "bytes"
--           , argType = TInterface Name { namespace = "GLib" , name = "Bytes" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the bytes containing the data"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "flags"
--           , argType =
--               TInterface
--                 Name { namespace = "Pango" , name = "LayoutDeserializeFlags" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "`PangoLayoutDeserializeFlags`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Layout" })
-- throws : True
-- Skip return : False

foreign import ccall "pango_layout_deserialize" pango_layout_deserialize :: 
    Ptr Pango.Context.Context ->            -- context : TInterface (Name {namespace = "Pango", name = "Context"})
    Ptr GLib.Bytes.Bytes ->                 -- bytes : TInterface (Name {namespace = "GLib", name = "Bytes"})
    CUInt ->                                -- flags : TInterface (Name {namespace = "Pango", name = "LayoutDeserializeFlags"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Layout)

-- | Loads data previously created via 'GI.Pango.Objects.Layout.layoutSerialize'.
-- 
-- For a discussion of the supported format, see that function.
-- 
-- Note: to verify that the returned layout is identical to
-- the one that was serialized, you can compare /@bytes@/ to the
-- result of serializing the layout again.
-- 
-- /Since: 1.50/
layoutDeserialize ::
    (B.CallStack.HasCallStack, MonadIO m, Pango.Context.IsContext a) =>
    a
    -- ^ /@context@/: a @PangoContext@
    -> GLib.Bytes.Bytes
    -- ^ /@bytes@/: the bytes containing the data
    -> [Pango.Flags.LayoutDeserializeFlags]
    -- ^ /@flags@/: @PangoLayoutDeserializeFlags@
    -> m (Maybe Layout)
    -- ^ __Returns:__ a new @PangoLayout@ /(Can throw 'Data.GI.Base.GError.GError')/
layoutDeserialize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsContext a) =>
a -> Bytes -> [LayoutDeserializeFlags] -> m (Maybe Layout)
layoutDeserialize a
context Bytes
bytes [LayoutDeserializeFlags]
flags = 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
$ do
    Ptr Context
context' <- a -> IO (Ptr Context)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Bytes
bytes' <- Bytes -> IO (Ptr Bytes)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Bytes
bytes
    let flags' :: CUInt
flags' = [LayoutDeserializeFlags] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [LayoutDeserializeFlags]
flags
    IO (Maybe Layout) -> IO () -> IO (Maybe Layout)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr Layout
result <- (Ptr (Ptr GError) -> IO (Ptr Layout)) -> IO (Ptr Layout)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr Layout)) -> IO (Ptr Layout))
-> (Ptr (Ptr GError) -> IO (Ptr Layout)) -> IO (Ptr Layout)
forall a b. (a -> b) -> a -> b
$ Ptr Context
-> Ptr Bytes -> CUInt -> Ptr (Ptr GError) -> IO (Ptr Layout)
pango_layout_deserialize Ptr Context
context' Ptr Bytes
bytes' CUInt
flags'
        Maybe Layout
maybeResult <- Ptr Layout -> (Ptr Layout -> IO Layout) -> IO (Maybe Layout)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Layout
result ((Ptr Layout -> IO Layout) -> IO (Maybe Layout))
-> (Ptr Layout -> IO Layout) -> IO (Maybe Layout)
forall a b. (a -> b) -> a -> b
$ \Ptr Layout
result' -> do
            Layout
result'' <- ((ManagedPtr Layout -> Layout) -> Ptr Layout -> IO Layout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Layout -> Layout
Layout) Ptr Layout
result'
            Layout -> IO Layout
forall (m :: * -> *) a. Monad m => a -> m a
return Layout
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
        Bytes -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Bytes
bytes
        Maybe Layout -> IO (Maybe Layout)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Layout
maybeResult
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
#endif