{-# LANGUAGE TypeApplications #-}
#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
Layout(..) ,
IsLayout ,
toLayout ,
#if defined(ENABLE_OVERLOADING)
ResolveLayoutMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
LayoutContextChangedMethodInfo ,
#endif
layoutContextChanged ,
#if defined(ENABLE_OVERLOADING)
LayoutCopyMethodInfo ,
#endif
layoutCopy ,
#if defined(ENABLE_OVERLOADING)
LayoutGetAlignmentMethodInfo ,
#endif
layoutGetAlignment ,
#if defined(ENABLE_OVERLOADING)
LayoutGetAttributesMethodInfo ,
#endif
layoutGetAttributes ,
#if defined(ENABLE_OVERLOADING)
LayoutGetAutoDirMethodInfo ,
#endif
layoutGetAutoDir ,
#if defined(ENABLE_OVERLOADING)
LayoutGetBaselineMethodInfo ,
#endif
layoutGetBaseline ,
#if defined(ENABLE_OVERLOADING)
LayoutGetCharacterCountMethodInfo ,
#endif
layoutGetCharacterCount ,
#if defined(ENABLE_OVERLOADING)
LayoutGetContextMethodInfo ,
#endif
layoutGetContext ,
#if defined(ENABLE_OVERLOADING)
LayoutGetCursorPosMethodInfo ,
#endif
layoutGetCursorPos ,
#if defined(ENABLE_OVERLOADING)
LayoutGetEllipsizeMethodInfo ,
#endif
layoutGetEllipsize ,
#if defined(ENABLE_OVERLOADING)
LayoutGetExtentsMethodInfo ,
#endif
layoutGetExtents ,
#if defined(ENABLE_OVERLOADING)
LayoutGetFontDescriptionMethodInfo ,
#endif
layoutGetFontDescription ,
#if defined(ENABLE_OVERLOADING)
LayoutGetHeightMethodInfo ,
#endif
layoutGetHeight ,
#if defined(ENABLE_OVERLOADING)
LayoutGetIndentMethodInfo ,
#endif
layoutGetIndent ,
#if defined(ENABLE_OVERLOADING)
LayoutGetIterMethodInfo ,
#endif
layoutGetIter ,
#if defined(ENABLE_OVERLOADING)
LayoutGetJustifyMethodInfo ,
#endif
layoutGetJustify ,
#if defined(ENABLE_OVERLOADING)
LayoutGetLineMethodInfo ,
#endif
layoutGetLine ,
#if defined(ENABLE_OVERLOADING)
LayoutGetLineCountMethodInfo ,
#endif
layoutGetLineCount ,
#if defined(ENABLE_OVERLOADING)
LayoutGetLineReadonlyMethodInfo ,
#endif
layoutGetLineReadonly ,
#if defined(ENABLE_OVERLOADING)
LayoutGetLineSpacingMethodInfo ,
#endif
layoutGetLineSpacing ,
#if defined(ENABLE_OVERLOADING)
LayoutGetLinesMethodInfo ,
#endif
layoutGetLines ,
#if defined(ENABLE_OVERLOADING)
LayoutGetLinesReadonlyMethodInfo ,
#endif
layoutGetLinesReadonly ,
#if defined(ENABLE_OVERLOADING)
LayoutGetLogAttrsMethodInfo ,
#endif
layoutGetLogAttrs ,
#if defined(ENABLE_OVERLOADING)
LayoutGetLogAttrsReadonlyMethodInfo ,
#endif
layoutGetLogAttrsReadonly ,
#if defined(ENABLE_OVERLOADING)
LayoutGetPixelExtentsMethodInfo ,
#endif
layoutGetPixelExtents ,
#if defined(ENABLE_OVERLOADING)
LayoutGetPixelSizeMethodInfo ,
#endif
layoutGetPixelSize ,
#if defined(ENABLE_OVERLOADING)
LayoutGetSerialMethodInfo ,
#endif
layoutGetSerial ,
#if defined(ENABLE_OVERLOADING)
LayoutGetSingleParagraphModeMethodInfo ,
#endif
layoutGetSingleParagraphMode ,
#if defined(ENABLE_OVERLOADING)
LayoutGetSizeMethodInfo ,
#endif
layoutGetSize ,
#if defined(ENABLE_OVERLOADING)
LayoutGetSpacingMethodInfo ,
#endif
layoutGetSpacing ,
#if defined(ENABLE_OVERLOADING)
LayoutGetTabsMethodInfo ,
#endif
layoutGetTabs ,
#if defined(ENABLE_OVERLOADING)
LayoutGetTextMethodInfo ,
#endif
layoutGetText ,
#if defined(ENABLE_OVERLOADING)
LayoutGetUnknownGlyphsCountMethodInfo ,
#endif
layoutGetUnknownGlyphsCount ,
#if defined(ENABLE_OVERLOADING)
LayoutGetWidthMethodInfo ,
#endif
layoutGetWidth ,
#if defined(ENABLE_OVERLOADING)
LayoutGetWrapMethodInfo ,
#endif
layoutGetWrap ,
#if defined(ENABLE_OVERLOADING)
LayoutIndexToLineXMethodInfo ,
#endif
layoutIndexToLineX ,
#if defined(ENABLE_OVERLOADING)
LayoutIndexToPosMethodInfo ,
#endif
layoutIndexToPos ,
#if defined(ENABLE_OVERLOADING)
LayoutIsEllipsizedMethodInfo ,
#endif
layoutIsEllipsized ,
#if defined(ENABLE_OVERLOADING)
LayoutIsWrappedMethodInfo ,
#endif
layoutIsWrapped ,
#if defined(ENABLE_OVERLOADING)
LayoutMoveCursorVisuallyMethodInfo ,
#endif
layoutMoveCursorVisually ,
layoutNew ,
#if defined(ENABLE_OVERLOADING)
LayoutSetAlignmentMethodInfo ,
#endif
layoutSetAlignment ,
#if defined(ENABLE_OVERLOADING)
LayoutSetAttributesMethodInfo ,
#endif
layoutSetAttributes ,
#if defined(ENABLE_OVERLOADING)
LayoutSetAutoDirMethodInfo ,
#endif
layoutSetAutoDir ,
#if defined(ENABLE_OVERLOADING)
LayoutSetEllipsizeMethodInfo ,
#endif
layoutSetEllipsize ,
#if defined(ENABLE_OVERLOADING)
LayoutSetFontDescriptionMethodInfo ,
#endif
layoutSetFontDescription ,
#if defined(ENABLE_OVERLOADING)
LayoutSetHeightMethodInfo ,
#endif
layoutSetHeight ,
#if defined(ENABLE_OVERLOADING)
LayoutSetIndentMethodInfo ,
#endif
layoutSetIndent ,
#if defined(ENABLE_OVERLOADING)
LayoutSetJustifyMethodInfo ,
#endif
layoutSetJustify ,
#if defined(ENABLE_OVERLOADING)
LayoutSetLineSpacingMethodInfo ,
#endif
layoutSetLineSpacing ,
#if defined(ENABLE_OVERLOADING)
LayoutSetMarkupMethodInfo ,
#endif
layoutSetMarkup ,
#if defined(ENABLE_OVERLOADING)
LayoutSetSingleParagraphModeMethodInfo ,
#endif
layoutSetSingleParagraphMode ,
#if defined(ENABLE_OVERLOADING)
LayoutSetSpacingMethodInfo ,
#endif
layoutSetSpacing ,
#if defined(ENABLE_OVERLOADING)
LayoutSetTabsMethodInfo ,
#endif
layoutSetTabs ,
#if defined(ENABLE_OVERLOADING)
LayoutSetTextMethodInfo ,
#endif
layoutSetText ,
#if defined(ENABLE_OVERLOADING)
LayoutSetWidthMethodInfo ,
#endif
layoutSetWidth ,
#if defined(ENABLE_OVERLOADING)
LayoutSetWrapMethodInfo ,
#endif
layoutSetWrap ,
#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.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Pango.Enums as Pango.Enums
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
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
instance B.GValue.IsGValue Layout where
toGValue :: Layout -> IO GValue
toGValue Layout
o = do
GType
gtype <- IO GType
c_pango_layout_get_type
Layout -> (Ptr Layout -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Layout
o (GType -> (GValue -> Ptr Layout -> IO ()) -> Ptr Layout -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr Layout -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO Layout
fromGValue GValue
gv = do
Ptr Layout
ptr <- GValue -> IO (Ptr Layout)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr Layout)
(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
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]
toLayout :: (MonadIO m, IsLayout o) => o -> m Layout
toLayout :: o -> m Layout
toLayout = IO Layout -> m Layout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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'
unsafeCastTo ManagedPtr Layout -> Layout
Layout
#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 "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 "xyToIndex" o = LayoutXyToIndexMethodInfo
ResolveLayoutMethod "getAlignment" o = LayoutGetAlignmentMethodInfo
ResolveLayoutMethod "getAttributes" o = LayoutGetAttributesMethodInfo
ResolveLayoutMethod "getAutoDir" o = LayoutGetAutoDirMethodInfo
ResolveLayoutMethod "getBaseline" o = LayoutGetBaselineMethodInfo
ResolveLayoutMethod "getCharacterCount" o = LayoutGetCharacterCountMethodInfo
ResolveLayoutMethod "getContext" o = LayoutGetContextMethodInfo
ResolveLayoutMethod "getCursorPos" o = LayoutGetCursorPosMethodInfo
ResolveLayoutMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
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 "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 "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.MethodInfo 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
#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
foreign import ccall "pango_layout_new" pango_layout_new ::
Ptr Pango.Context.Context ->
IO (Ptr Layout)
layoutNew ::
(B.CallStack.HasCallStack, MonadIO m, Pango.Context.IsContext a) =>
a
-> m Layout
layoutNew :: 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
foreign import ccall "pango_layout_context_changed" pango_layout_context_changed ::
Ptr Layout ->
IO ()
layoutContextChanged ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m ()
layoutContextChanged :: 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.MethodInfo LayoutContextChangedMethodInfo a signature where
overloadedMethod = layoutContextChanged
#endif
foreign import ccall "pango_layout_copy" pango_layout_copy ::
Ptr Layout ->
IO (Ptr Layout)
layoutCopy ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Layout
layoutCopy :: 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.MethodInfo LayoutCopyMethodInfo a signature where
overloadedMethod = layoutCopy
#endif
foreign import ccall "pango_layout_get_alignment" pango_layout_get_alignment ::
Ptr Layout ->
IO CUInt
layoutGetAlignment ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Pango.Enums.Alignment
layoutGetAlignment :: 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.MethodInfo LayoutGetAlignmentMethodInfo a signature where
overloadedMethod = layoutGetAlignment
#endif
foreign import ccall "pango_layout_get_attributes" pango_layout_get_attributes ::
Ptr Layout ->
IO (Ptr Pango.AttrList.AttrList)
layoutGetAttributes ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Pango.AttrList.AttrList
layoutGetAttributes :: a -> m AttrList
layoutGetAttributes a
layout = IO AttrList -> m AttrList
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO AttrList -> m AttrList) -> IO AttrList -> m 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'
Text -> Ptr AttrList -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"layoutGetAttributes" Ptr AttrList
result
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
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
layout
AttrList -> IO AttrList
forall (m :: * -> *) a. Monad m => a -> m a
return AttrList
result'
#if defined(ENABLE_OVERLOADING)
data LayoutGetAttributesMethodInfo
instance (signature ~ (m Pango.AttrList.AttrList), MonadIO m, IsLayout a) => O.MethodInfo LayoutGetAttributesMethodInfo a signature where
overloadedMethod = layoutGetAttributes
#endif
foreign import ccall "pango_layout_get_auto_dir" pango_layout_get_auto_dir ::
Ptr Layout ->
IO CInt
layoutGetAutoDir ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Bool
layoutGetAutoDir :: 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.MethodInfo LayoutGetAutoDirMethodInfo a signature where
overloadedMethod = layoutGetAutoDir
#endif
foreign import ccall "pango_layout_get_baseline" pango_layout_get_baseline ::
Ptr Layout ->
IO Int32
layoutGetBaseline ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Int32
layoutGetBaseline :: 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.MethodInfo LayoutGetBaselineMethodInfo a signature where
overloadedMethod = layoutGetBaseline
#endif
foreign import ccall "pango_layout_get_character_count" pango_layout_get_character_count ::
Ptr Layout ->
IO Int32
layoutGetCharacterCount ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Int32
layoutGetCharacterCount :: 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.MethodInfo LayoutGetCharacterCountMethodInfo a signature where
overloadedMethod = layoutGetCharacterCount
#endif
foreign import ccall "pango_layout_get_context" pango_layout_get_context ::
Ptr Layout ->
IO (Ptr Pango.Context.Context)
layoutGetContext ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Pango.Context.Context
layoutGetContext :: 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.MethodInfo LayoutGetContextMethodInfo a signature where
overloadedMethod = layoutGetContext
#endif
foreign import ccall "pango_layout_get_cursor_pos" pango_layout_get_cursor_pos ::
Ptr Layout ->
Int32 ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutGetCursorPos ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutGetCursorPos :: 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.MethodInfo LayoutGetCursorPosMethodInfo a signature where
overloadedMethod = layoutGetCursorPos
#endif
foreign import ccall "pango_layout_get_ellipsize" pango_layout_get_ellipsize ::
Ptr Layout ->
IO CUInt
layoutGetEllipsize ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Pango.Enums.EllipsizeMode
layoutGetEllipsize :: 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.MethodInfo LayoutGetEllipsizeMethodInfo a signature where
overloadedMethod = layoutGetEllipsize
#endif
foreign import ccall "pango_layout_get_extents" pango_layout_get_extents ::
Ptr Layout ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutGetExtents ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutGetExtents :: 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.MethodInfo LayoutGetExtentsMethodInfo a signature where
overloadedMethod = layoutGetExtents
#endif
foreign import ccall "pango_layout_get_font_description" pango_layout_get_font_description ::
Ptr Layout ->
IO (Ptr Pango.FontDescription.FontDescription)
layoutGetFontDescription ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m (Maybe Pango.FontDescription.FontDescription)
layoutGetFontDescription :: 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.MethodInfo LayoutGetFontDescriptionMethodInfo a signature where
overloadedMethod = layoutGetFontDescription
#endif
foreign import ccall "pango_layout_get_height" pango_layout_get_height ::
Ptr Layout ->
IO Int32
layoutGetHeight ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Int32
layoutGetHeight :: 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.MethodInfo LayoutGetHeightMethodInfo a signature where
overloadedMethod = layoutGetHeight
#endif
foreign import ccall "pango_layout_get_indent" pango_layout_get_indent ::
Ptr Layout ->
IO Int32
layoutGetIndent ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Int32
layoutGetIndent :: 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.MethodInfo LayoutGetIndentMethodInfo a signature where
overloadedMethod = layoutGetIndent
#endif
foreign import ccall "pango_layout_get_iter" pango_layout_get_iter ::
Ptr Layout ->
IO (Ptr Pango.LayoutIter.LayoutIter)
layoutGetIter ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Pango.LayoutIter.LayoutIter
layoutGetIter :: 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.MethodInfo LayoutGetIterMethodInfo a signature where
overloadedMethod = layoutGetIter
#endif
foreign import ccall "pango_layout_get_justify" pango_layout_get_justify ::
Ptr Layout ->
IO CInt
layoutGetJustify ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Bool
layoutGetJustify :: 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.MethodInfo LayoutGetJustifyMethodInfo a signature where
overloadedMethod = layoutGetJustify
#endif
foreign import ccall "pango_layout_get_line" pango_layout_get_line ::
Ptr Layout ->
Int32 ->
IO (Ptr Pango.LayoutLine.LayoutLine)
layoutGetLine ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> m (Maybe Pango.LayoutLine.LayoutLine)
layoutGetLine :: 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.MethodInfo LayoutGetLineMethodInfo a signature where
overloadedMethod = layoutGetLine
#endif
foreign import ccall "pango_layout_get_line_count" pango_layout_get_line_count ::
Ptr Layout ->
IO Int32
layoutGetLineCount ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Int32
layoutGetLineCount :: 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.MethodInfo LayoutGetLineCountMethodInfo a signature where
overloadedMethod = layoutGetLineCount
#endif
foreign import ccall "pango_layout_get_line_readonly" pango_layout_get_line_readonly ::
Ptr Layout ->
Int32 ->
IO (Ptr Pango.LayoutLine.LayoutLine)
layoutGetLineReadonly ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> m (Maybe Pango.LayoutLine.LayoutLine)
layoutGetLineReadonly :: 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.MethodInfo LayoutGetLineReadonlyMethodInfo a signature where
overloadedMethod = layoutGetLineReadonly
#endif
foreign import ccall "pango_layout_get_line_spacing" pango_layout_get_line_spacing ::
Ptr Layout ->
IO CFloat
layoutGetLineSpacing ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Float
layoutGetLineSpacing :: 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.MethodInfo LayoutGetLineSpacingMethodInfo a signature where
overloadedMethod = layoutGetLineSpacing
#endif
foreign import ccall "pango_layout_get_lines" pango_layout_get_lines ::
Ptr Layout ->
IO (Ptr (GSList (Ptr Pango.LayoutLine.LayoutLine)))
layoutGetLines ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m [Pango.LayoutLine.LayoutLine]
layoutGetLines :: 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.MethodInfo LayoutGetLinesMethodInfo a signature where
overloadedMethod = layoutGetLines
#endif
foreign import ccall "pango_layout_get_lines_readonly" pango_layout_get_lines_readonly ::
Ptr Layout ->
IO (Ptr (GSList (Ptr Pango.LayoutLine.LayoutLine)))
layoutGetLinesReadonly ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m [Pango.LayoutLine.LayoutLine]
layoutGetLinesReadonly :: 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.MethodInfo LayoutGetLinesReadonlyMethodInfo a signature where
overloadedMethod = layoutGetLinesReadonly
#endif
foreign import ccall "pango_layout_get_log_attrs" pango_layout_get_log_attrs ::
Ptr Layout ->
Ptr (Ptr Pango.LogAttr.LogAttr) ->
Ptr Int32 ->
IO ()
layoutGetLogAttrs ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m ([Pango.LogAttr.LogAttr])
layoutGetLogAttrs :: 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
52 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.MethodInfo LayoutGetLogAttrsMethodInfo a signature where
overloadedMethod = layoutGetLogAttrs
#endif
foreign import ccall "pango_layout_get_log_attrs_readonly" pango_layout_get_log_attrs_readonly ::
Ptr Layout ->
Ptr Int32 ->
IO (Ptr Pango.LogAttr.LogAttr)
layoutGetLogAttrsReadonly ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m [Pango.LogAttr.LogAttr]
layoutGetLogAttrsReadonly :: 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
52 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.MethodInfo LayoutGetLogAttrsReadonlyMethodInfo a signature where
overloadedMethod = layoutGetLogAttrsReadonly
#endif
foreign import ccall "pango_layout_get_pixel_extents" pango_layout_get_pixel_extents ::
Ptr Layout ->
Ptr Pango.Rectangle.Rectangle ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutGetPixelExtents ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m ((Pango.Rectangle.Rectangle, Pango.Rectangle.Rectangle))
layoutGetPixelExtents :: 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.MethodInfo LayoutGetPixelExtentsMethodInfo a signature where
overloadedMethod = layoutGetPixelExtents
#endif
foreign import ccall "pango_layout_get_pixel_size" pango_layout_get_pixel_size ::
Ptr Layout ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
layoutGetPixelSize ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m ((Int32, Int32))
layoutGetPixelSize :: 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.MethodInfo LayoutGetPixelSizeMethodInfo a signature where
overloadedMethod = layoutGetPixelSize
#endif
foreign import ccall "pango_layout_get_serial" pango_layout_get_serial ::
Ptr Layout ->
IO Word32
layoutGetSerial ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Word32
layoutGetSerial :: 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.MethodInfo LayoutGetSerialMethodInfo a signature where
overloadedMethod = layoutGetSerial
#endif
foreign import ccall "pango_layout_get_single_paragraph_mode" pango_layout_get_single_paragraph_mode ::
Ptr Layout ->
IO CInt
layoutGetSingleParagraphMode ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Bool
layoutGetSingleParagraphMode :: 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.MethodInfo LayoutGetSingleParagraphModeMethodInfo a signature where
overloadedMethod = layoutGetSingleParagraphMode
#endif
foreign import ccall "pango_layout_get_size" pango_layout_get_size ::
Ptr Layout ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
layoutGetSize ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m ((Int32, Int32))
layoutGetSize :: 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.MethodInfo LayoutGetSizeMethodInfo a signature where
overloadedMethod = layoutGetSize
#endif
foreign import ccall "pango_layout_get_spacing" pango_layout_get_spacing ::
Ptr Layout ->
IO Int32
layoutGetSpacing ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Int32
layoutGetSpacing :: 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.MethodInfo LayoutGetSpacingMethodInfo a signature where
overloadedMethod = layoutGetSpacing
#endif
foreign import ccall "pango_layout_get_tabs" pango_layout_get_tabs ::
Ptr Layout ->
IO (Ptr Pango.TabArray.TabArray)
layoutGetTabs ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m (Maybe Pango.TabArray.TabArray)
layoutGetTabs :: 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.MethodInfo LayoutGetTabsMethodInfo a signature where
overloadedMethod = layoutGetTabs
#endif
foreign import ccall "pango_layout_get_text" pango_layout_get_text ::
Ptr Layout ->
IO CString
layoutGetText ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m T.Text
layoutGetText :: 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.MethodInfo LayoutGetTextMethodInfo a signature where
overloadedMethod = layoutGetText
#endif
foreign import ccall "pango_layout_get_unknown_glyphs_count" pango_layout_get_unknown_glyphs_count ::
Ptr Layout ->
IO Int32
layoutGetUnknownGlyphsCount ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Int32
layoutGetUnknownGlyphsCount :: 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.MethodInfo LayoutGetUnknownGlyphsCountMethodInfo a signature where
overloadedMethod = layoutGetUnknownGlyphsCount
#endif
foreign import ccall "pango_layout_get_width" pango_layout_get_width ::
Ptr Layout ->
IO Int32
layoutGetWidth ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Int32
layoutGetWidth :: 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.MethodInfo LayoutGetWidthMethodInfo a signature where
overloadedMethod = layoutGetWidth
#endif
foreign import ccall "pango_layout_get_wrap" pango_layout_get_wrap ::
Ptr Layout ->
IO CUInt
layoutGetWrap ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Pango.Enums.WrapMode
layoutGetWrap :: 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.MethodInfo LayoutGetWrapMethodInfo a signature where
overloadedMethod = layoutGetWrap
#endif
foreign import ccall "pango_layout_index_to_line_x" pango_layout_index_to_line_x ::
Ptr Layout ->
Int32 ->
CInt ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
layoutIndexToLineX ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> Bool
-> m ((Int32, Int32))
layoutIndexToLineX :: 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.MethodInfo LayoutIndexToLineXMethodInfo a signature where
overloadedMethod = layoutIndexToLineX
#endif
foreign import ccall "pango_layout_index_to_pos" pango_layout_index_to_pos ::
Ptr Layout ->
Int32 ->
Ptr Pango.Rectangle.Rectangle ->
IO ()
layoutIndexToPos ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> m (Pango.Rectangle.Rectangle)
layoutIndexToPos :: 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.MethodInfo LayoutIndexToPosMethodInfo a signature where
overloadedMethod = layoutIndexToPos
#endif
foreign import ccall "pango_layout_is_ellipsized" pango_layout_is_ellipsized ::
Ptr Layout ->
IO CInt
layoutIsEllipsized ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Bool
layoutIsEllipsized :: 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.MethodInfo LayoutIsEllipsizedMethodInfo a signature where
overloadedMethod = layoutIsEllipsized
#endif
foreign import ccall "pango_layout_is_wrapped" pango_layout_is_wrapped ::
Ptr Layout ->
IO CInt
layoutIsWrapped ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> m Bool
layoutIsWrapped :: 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.MethodInfo LayoutIsWrappedMethodInfo a signature where
overloadedMethod = layoutIsWrapped
#endif
foreign import ccall "pango_layout_move_cursor_visually" pango_layout_move_cursor_visually ::
Ptr Layout ->
CInt ->
Int32 ->
Int32 ->
Int32 ->
Ptr Int32 ->
Ptr Int32 ->
IO ()
layoutMoveCursorVisually ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Bool
-> Int32
-> Int32
-> Int32
-> m ((Int32, Int32))
layoutMoveCursorVisually :: 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.MethodInfo LayoutMoveCursorVisuallyMethodInfo a signature where
overloadedMethod = layoutMoveCursorVisually
#endif
foreign import ccall "pango_layout_set_alignment" pango_layout_set_alignment ::
Ptr Layout ->
CUInt ->
IO ()
layoutSetAlignment ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Pango.Enums.Alignment
-> m ()
layoutSetAlignment :: 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.MethodInfo LayoutSetAlignmentMethodInfo a signature where
overloadedMethod = layoutSetAlignment
#endif
foreign import ccall "pango_layout_set_attributes" pango_layout_set_attributes ::
Ptr Layout ->
Ptr Pango.AttrList.AttrList ->
IO ()
layoutSetAttributes ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Maybe (Pango.AttrList.AttrList)
-> m ()
layoutSetAttributes :: 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.MethodInfo LayoutSetAttributesMethodInfo a signature where
overloadedMethod = layoutSetAttributes
#endif
foreign import ccall "pango_layout_set_auto_dir" pango_layout_set_auto_dir ::
Ptr Layout ->
CInt ->
IO ()
layoutSetAutoDir ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Bool
-> m ()
layoutSetAutoDir :: 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.MethodInfo LayoutSetAutoDirMethodInfo a signature where
overloadedMethod = layoutSetAutoDir
#endif
foreign import ccall "pango_layout_set_ellipsize" pango_layout_set_ellipsize ::
Ptr Layout ->
CUInt ->
IO ()
layoutSetEllipsize ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Pango.Enums.EllipsizeMode
-> m ()
layoutSetEllipsize :: 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.MethodInfo LayoutSetEllipsizeMethodInfo a signature where
overloadedMethod = layoutSetEllipsize
#endif
foreign import ccall "pango_layout_set_font_description" pango_layout_set_font_description ::
Ptr Layout ->
Ptr Pango.FontDescription.FontDescription ->
IO ()
layoutSetFontDescription ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Maybe (Pango.FontDescription.FontDescription)
-> m ()
layoutSetFontDescription :: 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.MethodInfo LayoutSetFontDescriptionMethodInfo a signature where
overloadedMethod = layoutSetFontDescription
#endif
foreign import ccall "pango_layout_set_height" pango_layout_set_height ::
Ptr Layout ->
Int32 ->
IO ()
layoutSetHeight ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> m ()
layoutSetHeight :: 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.MethodInfo LayoutSetHeightMethodInfo a signature where
overloadedMethod = layoutSetHeight
#endif
foreign import ccall "pango_layout_set_indent" pango_layout_set_indent ::
Ptr Layout ->
Int32 ->
IO ()
layoutSetIndent ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> m ()
layoutSetIndent :: 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.MethodInfo LayoutSetIndentMethodInfo a signature where
overloadedMethod = layoutSetIndent
#endif
foreign import ccall "pango_layout_set_justify" pango_layout_set_justify ::
Ptr Layout ->
CInt ->
IO ()
layoutSetJustify ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Bool
-> m ()
layoutSetJustify :: 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.MethodInfo LayoutSetJustifyMethodInfo a signature where
overloadedMethod = layoutSetJustify
#endif
foreign import ccall "pango_layout_set_line_spacing" pango_layout_set_line_spacing ::
Ptr Layout ->
CFloat ->
IO ()
layoutSetLineSpacing ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Float
-> m ()
layoutSetLineSpacing :: 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.MethodInfo LayoutSetLineSpacingMethodInfo a signature where
overloadedMethod = layoutSetLineSpacing
#endif
foreign import ccall "pango_layout_set_markup" pango_layout_set_markup ::
Ptr Layout ->
CString ->
Int32 ->
IO ()
layoutSetMarkup ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> T.Text
-> Int32
-> m ()
layoutSetMarkup :: 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.MethodInfo LayoutSetMarkupMethodInfo a signature where
overloadedMethod = layoutSetMarkup
#endif
#if defined(ENABLE_OVERLOADING)
data LayoutSetMarkupWithAccelMethodInfo
instance (p ~ (), o ~ O.UnsupportedMethodError "setMarkupWithAccel" Layout) => O.MethodInfo LayoutSetMarkupWithAccelMethodInfo o p where
overloadedMethod = undefined
#endif
foreign import ccall "pango_layout_set_single_paragraph_mode" pango_layout_set_single_paragraph_mode ::
Ptr Layout ->
CInt ->
IO ()
layoutSetSingleParagraphMode ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Bool
-> m ()
layoutSetSingleParagraphMode :: 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.MethodInfo LayoutSetSingleParagraphModeMethodInfo a signature where
overloadedMethod = layoutSetSingleParagraphMode
#endif
foreign import ccall "pango_layout_set_spacing" pango_layout_set_spacing ::
Ptr Layout ->
Int32 ->
IO ()
layoutSetSpacing ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> m ()
layoutSetSpacing :: 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.MethodInfo LayoutSetSpacingMethodInfo a signature where
overloadedMethod = layoutSetSpacing
#endif
foreign import ccall "pango_layout_set_tabs" pango_layout_set_tabs ::
Ptr Layout ->
Ptr Pango.TabArray.TabArray ->
IO ()
layoutSetTabs ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Maybe (Pango.TabArray.TabArray)
-> m ()
layoutSetTabs :: 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.MethodInfo LayoutSetTabsMethodInfo a signature where
overloadedMethod = layoutSetTabs
#endif
foreign import ccall "pango_layout_set_text" pango_layout_set_text ::
Ptr Layout ->
CString ->
Int32 ->
IO ()
layoutSetText ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> T.Text
-> Int32
-> m ()
layoutSetText :: 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.MethodInfo LayoutSetTextMethodInfo a signature where
overloadedMethod = layoutSetText
#endif
foreign import ccall "pango_layout_set_width" pango_layout_set_width ::
Ptr Layout ->
Int32 ->
IO ()
layoutSetWidth ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> m ()
layoutSetWidth :: 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.MethodInfo LayoutSetWidthMethodInfo a signature where
overloadedMethod = layoutSetWidth
#endif
foreign import ccall "pango_layout_set_wrap" pango_layout_set_wrap ::
Ptr Layout ->
CUInt ->
IO ()
layoutSetWrap ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Pango.Enums.WrapMode
-> m ()
layoutSetWrap :: 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.MethodInfo LayoutSetWrapMethodInfo a signature where
overloadedMethod = layoutSetWrap
#endif
foreign import ccall "pango_layout_xy_to_index" pango_layout_xy_to_index ::
Ptr Layout ->
Int32 ->
Int32 ->
Ptr Int32 ->
Ptr Int32 ->
IO CInt
layoutXyToIndex ::
(B.CallStack.HasCallStack, MonadIO m, IsLayout a) =>
a
-> Int32
-> Int32
-> m ((Bool, Int32, Int32))
layoutXyToIndex :: 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.MethodInfo LayoutXyToIndexMethodInfo a signature where
overloadedMethod = layoutXyToIndex
#endif