{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @PangoRenderer@ is a base class for objects that can render text
-- provided as @PangoGlyphString@ or @PangoLayout@.
-- 
-- By subclassing @PangoRenderer@ and overriding operations such as
-- /@drawGlyphs@/ and /@drawRectangle@/, renderers for particular font
-- backends and destinations can be created.
-- 
-- /Since: 1.8/

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

module GI.Pango.Objects.Renderer
    ( 

-- * Exported types
    Renderer(..)                            ,
    IsRenderer                              ,
    toRenderer                              ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [activate]("GI.Pango.Objects.Renderer#g:method:activate"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [deactivate]("GI.Pango.Objects.Renderer#g:method:deactivate"), [drawErrorUnderline]("GI.Pango.Objects.Renderer#g:method:drawErrorUnderline"), [drawGlyph]("GI.Pango.Objects.Renderer#g:method:drawGlyph"), [drawGlyphItem]("GI.Pango.Objects.Renderer#g:method:drawGlyphItem"), [drawGlyphs]("GI.Pango.Objects.Renderer#g:method:drawGlyphs"), [drawLayout]("GI.Pango.Objects.Renderer#g:method:drawLayout"), [drawLayoutLine]("GI.Pango.Objects.Renderer#g:method:drawLayoutLine"), [drawRectangle]("GI.Pango.Objects.Renderer#g:method:drawRectangle"), [drawTrapezoid]("GI.Pango.Objects.Renderer#g:method:drawTrapezoid"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [partChanged]("GI.Pango.Objects.Renderer#g:method:partChanged"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAlpha]("GI.Pango.Objects.Renderer#g:method:getAlpha"), [getColor]("GI.Pango.Objects.Renderer#g:method:getColor"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getLayout]("GI.Pango.Objects.Renderer#g:method:getLayout"), [getLayoutLine]("GI.Pango.Objects.Renderer#g:method:getLayoutLine"), [getMatrix]("GI.Pango.Objects.Renderer#g:method:getMatrix"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setAlpha]("GI.Pango.Objects.Renderer#g:method:setAlpha"), [setColor]("GI.Pango.Objects.Renderer#g:method:setColor"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setMatrix]("GI.Pango.Objects.Renderer#g:method:setMatrix"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveRendererMethod                   ,
#endif

-- ** activate #method:activate#

#if defined(ENABLE_OVERLOADING)
    RendererActivateMethodInfo              ,
#endif
    rendererActivate                        ,


-- ** deactivate #method:deactivate#

#if defined(ENABLE_OVERLOADING)
    RendererDeactivateMethodInfo            ,
#endif
    rendererDeactivate                      ,


-- ** drawErrorUnderline #method:drawErrorUnderline#

#if defined(ENABLE_OVERLOADING)
    RendererDrawErrorUnderlineMethodInfo    ,
#endif
    rendererDrawErrorUnderline              ,


-- ** drawGlyph #method:drawGlyph#

#if defined(ENABLE_OVERLOADING)
    RendererDrawGlyphMethodInfo             ,
#endif
    rendererDrawGlyph                       ,


-- ** drawGlyphItem #method:drawGlyphItem#

#if defined(ENABLE_OVERLOADING)
    RendererDrawGlyphItemMethodInfo         ,
#endif
    rendererDrawGlyphItem                   ,


-- ** drawGlyphs #method:drawGlyphs#

#if defined(ENABLE_OVERLOADING)
    RendererDrawGlyphsMethodInfo            ,
#endif
    rendererDrawGlyphs                      ,


-- ** drawLayout #method:drawLayout#

#if defined(ENABLE_OVERLOADING)
    RendererDrawLayoutMethodInfo            ,
#endif
    rendererDrawLayout                      ,


-- ** drawLayoutLine #method:drawLayoutLine#

#if defined(ENABLE_OVERLOADING)
    RendererDrawLayoutLineMethodInfo        ,
#endif
    rendererDrawLayoutLine                  ,


-- ** drawRectangle #method:drawRectangle#

#if defined(ENABLE_OVERLOADING)
    RendererDrawRectangleMethodInfo         ,
#endif
    rendererDrawRectangle                   ,


-- ** drawTrapezoid #method:drawTrapezoid#

#if defined(ENABLE_OVERLOADING)
    RendererDrawTrapezoidMethodInfo         ,
#endif
    rendererDrawTrapezoid                   ,


-- ** getAlpha #method:getAlpha#

#if defined(ENABLE_OVERLOADING)
    RendererGetAlphaMethodInfo              ,
#endif
    rendererGetAlpha                        ,


-- ** getColor #method:getColor#

#if defined(ENABLE_OVERLOADING)
    RendererGetColorMethodInfo              ,
#endif
    rendererGetColor                        ,


-- ** getLayout #method:getLayout#

#if defined(ENABLE_OVERLOADING)
    RendererGetLayoutMethodInfo             ,
#endif
    rendererGetLayout                       ,


-- ** getLayoutLine #method:getLayoutLine#

#if defined(ENABLE_OVERLOADING)
    RendererGetLayoutLineMethodInfo         ,
#endif
    rendererGetLayoutLine                   ,


-- ** getMatrix #method:getMatrix#

#if defined(ENABLE_OVERLOADING)
    RendererGetMatrixMethodInfo             ,
#endif
    rendererGetMatrix                       ,


-- ** partChanged #method:partChanged#

#if defined(ENABLE_OVERLOADING)
    RendererPartChangedMethodInfo           ,
#endif
    rendererPartChanged                     ,


-- ** setAlpha #method:setAlpha#

#if defined(ENABLE_OVERLOADING)
    RendererSetAlphaMethodInfo              ,
#endif
    rendererSetAlpha                        ,


-- ** setColor #method:setColor#

#if defined(ENABLE_OVERLOADING)
    RendererSetColorMethodInfo              ,
#endif
    rendererSetColor                        ,


-- ** setMatrix #method:setMatrix#

#if defined(ENABLE_OVERLOADING)
    RendererSetMatrixMethodInfo             ,
#endif
    rendererSetMatrix                       ,




    ) where

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

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

import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Pango.Enums as Pango.Enums
import {-# SOURCE #-} qualified GI.Pango.Objects.Font as Pango.Font
import {-# SOURCE #-} qualified GI.Pango.Objects.Layout as Pango.Layout
import {-# SOURCE #-} qualified GI.Pango.Structs.Color as Pango.Color
import {-# SOURCE #-} qualified GI.Pango.Structs.GlyphItem as Pango.GlyphItem
import {-# SOURCE #-} qualified GI.Pango.Structs.GlyphString as Pango.GlyphString
import {-# SOURCE #-} qualified GI.Pango.Structs.LayoutLine as Pango.LayoutLine
import {-# SOURCE #-} qualified GI.Pango.Structs.Matrix as Pango.Matrix

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

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

foreign import ccall "pango_renderer_get_type"
    c_pango_renderer_get_type :: IO B.Types.GType

instance B.Types.TypedObject Renderer where
    glibType :: IO GType
glibType = IO GType
c_pango_renderer_get_type

instance B.Types.GObject Renderer

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolveRendererMethod (t :: Symbol) (o :: *) :: * where
    ResolveRendererMethod "activate" o = RendererActivateMethodInfo
    ResolveRendererMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveRendererMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveRendererMethod "deactivate" o = RendererDeactivateMethodInfo
    ResolveRendererMethod "drawErrorUnderline" o = RendererDrawErrorUnderlineMethodInfo
    ResolveRendererMethod "drawGlyph" o = RendererDrawGlyphMethodInfo
    ResolveRendererMethod "drawGlyphItem" o = RendererDrawGlyphItemMethodInfo
    ResolveRendererMethod "drawGlyphs" o = RendererDrawGlyphsMethodInfo
    ResolveRendererMethod "drawLayout" o = RendererDrawLayoutMethodInfo
    ResolveRendererMethod "drawLayoutLine" o = RendererDrawLayoutLineMethodInfo
    ResolveRendererMethod "drawRectangle" o = RendererDrawRectangleMethodInfo
    ResolveRendererMethod "drawTrapezoid" o = RendererDrawTrapezoidMethodInfo
    ResolveRendererMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveRendererMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveRendererMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveRendererMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveRendererMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveRendererMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveRendererMethod "partChanged" o = RendererPartChangedMethodInfo
    ResolveRendererMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveRendererMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveRendererMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveRendererMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveRendererMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveRendererMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveRendererMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveRendererMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveRendererMethod "getAlpha" o = RendererGetAlphaMethodInfo
    ResolveRendererMethod "getColor" o = RendererGetColorMethodInfo
    ResolveRendererMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveRendererMethod "getLayout" o = RendererGetLayoutMethodInfo
    ResolveRendererMethod "getLayoutLine" o = RendererGetLayoutLineMethodInfo
    ResolveRendererMethod "getMatrix" o = RendererGetMatrixMethodInfo
    ResolveRendererMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveRendererMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveRendererMethod "setAlpha" o = RendererSetAlphaMethodInfo
    ResolveRendererMethod "setColor" o = RendererSetColorMethodInfo
    ResolveRendererMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveRendererMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveRendererMethod "setMatrix" o = RendererSetMatrixMethodInfo
    ResolveRendererMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveRendererMethod l o = O.MethodResolutionFailed l o

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

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

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

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

foreign import ccall "pango_renderer_activate" pango_renderer_activate :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    IO ()

-- | Does initial setup before rendering operations on /@renderer@/.
-- 
-- 'GI.Pango.Objects.Renderer.rendererDeactivate' should be called when done drawing.
-- Calls such as 'GI.Pango.Objects.Renderer.rendererDrawLayout' automatically
-- activate the layout before drawing on it.
-- 
-- Calls to 'GI.Pango.Objects.Renderer.rendererActivate' and
-- 'GI.Pango.Objects.Renderer.rendererDeactivate' can be nested and the
-- renderer will only be initialized and deinitialized once.
-- 
-- /Since: 1.8/
rendererActivate ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> m ()
rendererActivate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> m ()
rendererActivate a
renderer = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Renderer -> IO ()
pango_renderer_activate Ptr Renderer
renderer'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererActivateMethodInfo
instance (signature ~ (m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererActivateMethodInfo a signature where
    overloadedMethod = rendererActivate

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


#endif

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

foreign import ccall "pango_renderer_deactivate" pango_renderer_deactivate :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    IO ()

-- | Cleans up after rendering operations on /@renderer@/.
-- 
-- See docs for 'GI.Pango.Objects.Renderer.rendererActivate'.
-- 
-- /Since: 1.8/
rendererDeactivate ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> m ()
rendererDeactivate :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> m ()
rendererDeactivate a
renderer = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Renderer -> IO ()
pango_renderer_deactivate Ptr Renderer
renderer'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererDeactivateMethodInfo
instance (signature ~ (m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererDeactivateMethodInfo a signature where
    overloadedMethod = rendererDeactivate

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


#endif

-- method Renderer::draw_error_underline
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "X coordinate of underline, in Pango units in user coordinate system"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Y coordinate of underline, in Pango units in user coordinate system"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "width of underline, in Pango units in user coordinate system"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "height of underline, in Pango units in user coordinate system"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_draw_error_underline" pango_renderer_draw_error_underline :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Draw a squiggly line that approximately covers the given rectangle
-- in the style of an underline used to indicate a spelling error.
-- 
-- The width of the underline is rounded to an integer number
-- of up\/down segments and the resulting rectangle is centered
-- in the original rectangle.
-- 
-- This should be called while /@renderer@/ is already active.
-- Use 'GI.Pango.Objects.Renderer.rendererActivate' to activate a renderer.
-- 
-- /Since: 1.8/
rendererDrawErrorUnderline ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Int32
    -- ^ /@x@/: X coordinate of underline, in Pango units in user coordinate system
    -> Int32
    -- ^ /@y@/: Y coordinate of underline, in Pango units in user coordinate system
    -> Int32
    -- ^ /@width@/: width of underline, in Pango units in user coordinate system
    -> Int32
    -- ^ /@height@/: height of underline, in Pango units in user coordinate system
    -> m ()
rendererDrawErrorUnderline :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
rendererDrawErrorUnderline a
renderer Int32
x Int32
y Int32
width 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Renderer -> Int32 -> Int32 -> Int32 -> Int32 -> IO ()
pango_renderer_draw_error_underline Ptr Renderer
renderer' Int32
x Int32
y Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererDrawErrorUnderlineMethodInfo
instance (signature ~ (Int32 -> Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererDrawErrorUnderlineMethodInfo a signature where
    overloadedMethod = rendererDrawErrorUnderline

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


#endif

-- method Renderer::draw_glyph
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoFont`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "glyph"
--           , argType = TBasicType TUInt32
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the glyph index of a single glyph"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "X coordinate of left edge of baseline of glyph"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "Y coordinate of left edge of baseline of glyph"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_draw_glyph" pango_renderer_draw_glyph :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    Ptr Pango.Font.Font ->                  -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    Word32 ->                               -- glyph : TBasicType TUInt32
    CDouble ->                              -- x : TBasicType TDouble
    CDouble ->                              -- y : TBasicType TDouble
    IO ()

-- | Draws a single glyph with coordinates in device space.
-- 
-- /Since: 1.8/
rendererDrawGlyph ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a, Pango.Font.IsFont b) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> b
    -- ^ /@font@/: a @PangoFont@
    -> Word32
    -- ^ /@glyph@/: the glyph index of a single glyph
    -> Double
    -- ^ /@x@/: X coordinate of left edge of baseline of glyph
    -> Double
    -- ^ /@y@/: Y coordinate of left edge of baseline of glyph
    -> m ()
rendererDrawGlyph :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRenderer a, IsFont b) =>
a -> b -> Word32 -> Double -> Double -> m ()
rendererDrawGlyph a
renderer b
font Word32
glyph Double
x Double
y = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Font
font' <- b -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
font
    let x' :: CDouble
x' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x
    let y' :: CDouble
y' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y
    Ptr Renderer -> Ptr Font -> Word32 -> CDouble -> CDouble -> IO ()
pango_renderer_draw_glyph Ptr Renderer
renderer' Ptr Font
font' Word32
glyph CDouble
x' CDouble
y'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
font
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererDrawGlyphMethodInfo
instance (signature ~ (b -> Word32 -> Double -> Double -> m ()), MonadIO m, IsRenderer a, Pango.Font.IsFont b) => O.OverloadedMethod RendererDrawGlyphMethodInfo a signature where
    overloadedMethod = rendererDrawGlyph

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


#endif

-- method Renderer::draw_glyph_item
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "text"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the UTF-8 text that @glyph_item refers to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "glyph_item"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "GlyphItem" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoGlyphItem`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "X position of left edge of baseline, in user space coordinates\n  in Pango units"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Y position of left edge of baseline, in user space coordinates\n  in Pango units"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_draw_glyph_item" pango_renderer_draw_glyph_item :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    CString ->                              -- text : TBasicType TUTF8
    Ptr Pango.GlyphItem.GlyphItem ->        -- glyph_item : TInterface (Name {namespace = "Pango", name = "GlyphItem"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO ()

-- | Draws the glyphs in /@glyphItem@/ with the specified @PangoRenderer@,
-- embedding the text associated with the glyphs in the output if the
-- output format supports it.
-- 
-- This is useful for rendering text in PDF.
-- 
-- Note that this method does not handle attributes in /@glyphItem@/.
-- If you want colors, shapes and lines handled automatically according
-- to those attributes, you need to use 'GI.Pango.Objects.Renderer.rendererDrawLayoutLine'
-- or 'GI.Pango.Objects.Renderer.rendererDrawLayout'.
-- 
-- Note that /@text@/ is the start of the text for layout, which is then
-- indexed by @glyph_item->item->offset@.
-- 
-- If /@text@/ is 'P.Nothing', this simply calls 'GI.Pango.Objects.Renderer.rendererDrawGlyphs'.
-- 
-- The default implementation of this method simply falls back to
-- 'GI.Pango.Objects.Renderer.rendererDrawGlyphs'.
-- 
-- /Since: 1.22/
rendererDrawGlyphItem ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Maybe (T.Text)
    -- ^ /@text@/: the UTF-8 text that /@glyphItem@/ refers to
    -> Pango.GlyphItem.GlyphItem
    -- ^ /@glyphItem@/: a @PangoGlyphItem@
    -> Int32
    -- ^ /@x@/: X position of left edge of baseline, in user space coordinates
    --   in Pango units
    -> Int32
    -- ^ /@y@/: Y position of left edge of baseline, in user space coordinates
    --   in Pango units
    -> m ()
rendererDrawGlyphItem :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> Maybe Text -> GlyphItem -> Int32 -> Int32 -> m ()
rendererDrawGlyphItem a
renderer Maybe Text
text GlyphItem
glyphItem Int32
x Int32
y = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr CChar
maybeText <- case Maybe Text
text of
        Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
nullPtr
        Just Text
jText -> do
            Ptr CChar
jText' <- Text -> IO (Ptr CChar)
textToCString Text
jText
            Ptr CChar -> IO (Ptr CChar)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
jText'
    Ptr GlyphItem
glyphItem' <- GlyphItem -> IO (Ptr GlyphItem)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphItem
glyphItem
    Ptr Renderer
-> Ptr CChar -> Ptr GlyphItem -> Int32 -> Int32 -> IO ()
pango_renderer_draw_glyph_item Ptr Renderer
renderer' Ptr CChar
maybeText Ptr GlyphItem
glyphItem' Int32
x Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    GlyphItem -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphItem
glyphItem
    Ptr CChar -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CChar
maybeText
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererDrawGlyphItemMethodInfo
instance (signature ~ (Maybe (T.Text) -> Pango.GlyphItem.GlyphItem -> Int32 -> Int32 -> m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererDrawGlyphItemMethodInfo a signature where
    overloadedMethod = rendererDrawGlyphItem

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


#endif

-- method Renderer::draw_glyphs
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "font"
--           , argType = TInterface Name { namespace = "Pango" , name = "Font" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoFont`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "glyphs"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "GlyphString" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoGlyphString`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "X position of left edge of baseline, in user space coordinates\n  in Pango units."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Y position of left edge of baseline, in user space coordinates\n  in Pango units."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_draw_glyphs" pango_renderer_draw_glyphs :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    Ptr Pango.Font.Font ->                  -- font : TInterface (Name {namespace = "Pango", name = "Font"})
    Ptr Pango.GlyphString.GlyphString ->    -- glyphs : TInterface (Name {namespace = "Pango", name = "GlyphString"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO ()

-- | Draws the glyphs in /@glyphs@/ with the specified @PangoRenderer@.
-- 
-- /Since: 1.8/
rendererDrawGlyphs ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a, Pango.Font.IsFont b) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> b
    -- ^ /@font@/: a @PangoFont@
    -> Pango.GlyphString.GlyphString
    -- ^ /@glyphs@/: a @PangoGlyphString@
    -> Int32
    -- ^ /@x@/: X position of left edge of baseline, in user space coordinates
    --   in Pango units.
    -> Int32
    -- ^ /@y@/: Y position of left edge of baseline, in user space coordinates
    --   in Pango units.
    -> m ()
rendererDrawGlyphs :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRenderer a, IsFont b) =>
a -> b -> GlyphString -> Int32 -> Int32 -> m ()
rendererDrawGlyphs a
renderer b
font GlyphString
glyphs Int32
x Int32
y = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Font
font' <- b -> IO (Ptr Font)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
font
    Ptr GlyphString
glyphs' <- GlyphString -> IO (Ptr GlyphString)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GlyphString
glyphs
    Ptr Renderer
-> Ptr Font -> Ptr GlyphString -> Int32 -> Int32 -> IO ()
pango_renderer_draw_glyphs Ptr Renderer
renderer' Ptr Font
font' Ptr GlyphString
glyphs' Int32
x Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
font
    GlyphString -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GlyphString
glyphs
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererDrawGlyphsMethodInfo
instance (signature ~ (b -> Pango.GlyphString.GlyphString -> Int32 -> Int32 -> m ()), MonadIO m, IsRenderer a, Pango.Font.IsFont b) => O.OverloadedMethod RendererDrawGlyphsMethodInfo a signature where
    overloadedMethod = rendererDrawGlyphs

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


#endif

-- method Renderer::draw_layout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "layout"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Layout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayout`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "X position of left edge of baseline, in user space coordinates\n  in Pango units."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Y position of left edge of baseline, in user space coordinates\n  in Pango units."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_draw_layout" pango_renderer_draw_layout :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    Ptr Pango.Layout.Layout ->              -- layout : TInterface (Name {namespace = "Pango", name = "Layout"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO ()

-- | Draws /@layout@/ with the specified @PangoRenderer@.
-- 
-- This is equivalent to drawing the lines of the layout, at their
-- respective positions relative to /@x@/, /@y@/.
-- 
-- /Since: 1.8/
rendererDrawLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a, Pango.Layout.IsLayout b) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> b
    -- ^ /@layout@/: a @PangoLayout@
    -> Int32
    -- ^ /@x@/: X position of left edge of baseline, in user space coordinates
    --   in Pango units.
    -> Int32
    -- ^ /@y@/: Y position of left edge of baseline, in user space coordinates
    --   in Pango units.
    -> m ()
rendererDrawLayout :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsRenderer a, IsLayout b) =>
a -> b -> Int32 -> Int32 -> m ()
rendererDrawLayout a
renderer b
layout Int32
x Int32
y = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Layout
layout' <- b -> IO (Ptr Layout)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
layout
    Ptr Renderer -> Ptr Layout -> Int32 -> Int32 -> IO ()
pango_renderer_draw_layout Ptr Renderer
renderer' Ptr Layout
layout' Int32
x Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
layout
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererDrawLayoutMethodInfo
instance (signature ~ (b -> Int32 -> Int32 -> m ()), MonadIO m, IsRenderer a, Pango.Layout.IsLayout b) => O.OverloadedMethod RendererDrawLayoutMethodInfo a signature where
    overloadedMethod = rendererDrawLayout

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


#endif

-- method Renderer::draw_layout_line
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "line"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "LayoutLine" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoLayoutLine`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "X position of left edge of baseline, in user space coordinates\n  in Pango units."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Y position of left edge of baseline, in user space coordinates\n  in Pango units."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_draw_layout_line" pango_renderer_draw_layout_line :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    Ptr Pango.LayoutLine.LayoutLine ->      -- line : TInterface (Name {namespace = "Pango", name = "LayoutLine"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    IO ()

-- | Draws /@line@/ with the specified @PangoRenderer@.
-- 
-- This draws the glyph items that make up the line, as well as
-- shapes, backgrounds and lines that are specified by the attributes
-- of those items.
-- 
-- /Since: 1.8/
rendererDrawLayoutLine ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Pango.LayoutLine.LayoutLine
    -- ^ /@line@/: a @PangoLayoutLine@
    -> Int32
    -- ^ /@x@/: X position of left edge of baseline, in user space coordinates
    --   in Pango units.
    -> Int32
    -- ^ /@y@/: Y position of left edge of baseline, in user space coordinates
    --   in Pango units.
    -> m ()
rendererDrawLayoutLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> LayoutLine -> Int32 -> Int32 -> m ()
rendererDrawLayoutLine a
renderer LayoutLine
line Int32
x Int32
y = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr LayoutLine
line' <- LayoutLine -> IO (Ptr LayoutLine)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr LayoutLine
line
    Ptr Renderer -> Ptr LayoutLine -> Int32 -> Int32 -> IO ()
pango_renderer_draw_layout_line Ptr Renderer
renderer' Ptr LayoutLine
line' Int32
x Int32
y
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    LayoutLine -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr LayoutLine
line
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererDrawLayoutLineMethodInfo
instance (signature ~ (Pango.LayoutLine.LayoutLine -> Int32 -> Int32 -> m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererDrawLayoutLineMethodInfo a signature where
    overloadedMethod = rendererDrawLayoutLine

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


#endif

-- method Renderer::draw_rectangle
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "part"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "RenderPart" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "type of object this rectangle is part of"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "X position at which to draw rectangle, in user space coordinates\n  in Pango units"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "Y position at which to draw rectangle, in user space coordinates\n  in Pango units"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "width of rectangle in Pango units"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "height of rectangle in Pango units"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_draw_rectangle" pango_renderer_draw_rectangle :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    CUInt ->                                -- part : TInterface (Name {namespace = "Pango", name = "RenderPart"})
    Int32 ->                                -- x : TBasicType TInt
    Int32 ->                                -- y : TBasicType TInt
    Int32 ->                                -- width : TBasicType TInt
    Int32 ->                                -- height : TBasicType TInt
    IO ()

-- | Draws an axis-aligned rectangle in user space coordinates with the
-- specified @PangoRenderer@.
-- 
-- This should be called while /@renderer@/ is already active.
-- Use 'GI.Pango.Objects.Renderer.rendererActivate' to activate a renderer.
-- 
-- /Since: 1.8/
rendererDrawRectangle ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Pango.Enums.RenderPart
    -- ^ /@part@/: type of object this rectangle is part of
    -> Int32
    -- ^ /@x@/: X position at which to draw rectangle, in user space coordinates
    --   in Pango units
    -> Int32
    -- ^ /@y@/: Y position at which to draw rectangle, in user space coordinates
    --   in Pango units
    -> Int32
    -- ^ /@width@/: width of rectangle in Pango units
    -> Int32
    -- ^ /@height@/: height of rectangle in Pango units
    -> m ()
rendererDrawRectangle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> RenderPart -> Int32 -> Int32 -> Int32 -> Int32 -> m ()
rendererDrawRectangle a
renderer RenderPart
part Int32
x Int32
y Int32
width 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    let part' :: CUInt
part' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RenderPart -> Int) -> RenderPart -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderPart -> Int
forall a. Enum a => a -> Int
fromEnum) RenderPart
part
    Ptr Renderer -> CUInt -> Int32 -> Int32 -> Int32 -> Int32 -> IO ()
pango_renderer_draw_rectangle Ptr Renderer
renderer' CUInt
part' Int32
x Int32
y Int32
width Int32
height
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererDrawRectangleMethodInfo
instance (signature ~ (Pango.Enums.RenderPart -> Int32 -> Int32 -> Int32 -> Int32 -> m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererDrawRectangleMethodInfo a signature where
    overloadedMethod = rendererDrawRectangle

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


#endif

-- method Renderer::draw_trapezoid
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "part"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "RenderPart" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "type of object this trapezoid is part of"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y1_"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Y coordinate of top of trapezoid"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x11"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "X coordinate of left end of top of trapezoid"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x21"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "X coordinate of right end of top of trapezoid"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "y2"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "Y coordinate of bottom of trapezoid"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x12"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "X coordinate of left end of bottom of trapezoid"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "x22"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "X coordinate of right end of bottom of trapezoid"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_draw_trapezoid" pango_renderer_draw_trapezoid :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    CUInt ->                                -- part : TInterface (Name {namespace = "Pango", name = "RenderPart"})
    CDouble ->                              -- y1_ : TBasicType TDouble
    CDouble ->                              -- x11 : TBasicType TDouble
    CDouble ->                              -- x21 : TBasicType TDouble
    CDouble ->                              -- y2 : TBasicType TDouble
    CDouble ->                              -- x12 : TBasicType TDouble
    CDouble ->                              -- x22 : TBasicType TDouble
    IO ()

-- | Draws a trapezoid with the parallel sides aligned with the X axis
-- using the given @PangoRenderer@; coordinates are in device space.
-- 
-- /Since: 1.8/
rendererDrawTrapezoid ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Pango.Enums.RenderPart
    -- ^ /@part@/: type of object this trapezoid is part of
    -> Double
    -- ^ /@y1_@/: Y coordinate of top of trapezoid
    -> Double
    -- ^ /@x11@/: X coordinate of left end of top of trapezoid
    -> Double
    -- ^ /@x21@/: X coordinate of right end of top of trapezoid
    -> Double
    -- ^ /@y2@/: Y coordinate of bottom of trapezoid
    -> Double
    -- ^ /@x12@/: X coordinate of left end of bottom of trapezoid
    -> Double
    -- ^ /@x22@/: X coordinate of right end of bottom of trapezoid
    -> m ()
rendererDrawTrapezoid :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a
-> RenderPart
-> Double
-> Double
-> Double
-> Double
-> Double
-> Double
-> m ()
rendererDrawTrapezoid a
renderer RenderPart
part Double
y1_ Double
x11 Double
x21 Double
y2 Double
x12 Double
x22 = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    let part' :: CUInt
part' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RenderPart -> Int) -> RenderPart -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderPart -> Int
forall a. Enum a => a -> Int
fromEnum) RenderPart
part
    let y1_' :: CDouble
y1_' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y1_
    let x11' :: CDouble
x11' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x11
    let x21' :: CDouble
x21' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x21
    let y2' :: CDouble
y2' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
y2
    let x12' :: CDouble
x12' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x12
    let x22' :: CDouble
x22' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
x22
    Ptr Renderer
-> CUInt
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> CDouble
-> IO ()
pango_renderer_draw_trapezoid Ptr Renderer
renderer' CUInt
part' CDouble
y1_' CDouble
x11' CDouble
x21' CDouble
y2' CDouble
x12' CDouble
x22'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererDrawTrapezoidMethodInfo
instance (signature ~ (Pango.Enums.RenderPart -> Double -> Double -> Double -> Double -> Double -> Double -> m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererDrawTrapezoidMethodInfo a signature where
    overloadedMethod = rendererDrawTrapezoid

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


#endif

-- method Renderer::get_alpha
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "part"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "RenderPart" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the part to get the alpha for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUInt16)
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_get_alpha" pango_renderer_get_alpha :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    CUInt ->                                -- part : TInterface (Name {namespace = "Pango", name = "RenderPart"})
    IO Word16

-- | Gets the current alpha for the specified part.
-- 
-- /Since: 1.38/
rendererGetAlpha ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Pango.Enums.RenderPart
    -- ^ /@part@/: the part to get the alpha for
    -> m Word16
    -- ^ __Returns:__ the alpha for the specified part,
    --   or 0 if it hasn\'t been set and should be
    --   inherited from the environment.
rendererGetAlpha :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> RenderPart -> m Word16
rendererGetAlpha a
renderer RenderPart
part = IO Word16 -> m Word16
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Word16 -> m Word16) -> IO Word16 -> m Word16
forall a b. (a -> b) -> a -> b
$ do
    Ptr Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    let part' :: CUInt
part' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RenderPart -> Int) -> RenderPart -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderPart -> Int
forall a. Enum a => a -> Int
fromEnum) RenderPart
part
    Word16
result <- Ptr Renderer -> CUInt -> IO Word16
pango_renderer_get_alpha Ptr Renderer
renderer' CUInt
part'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Word16 -> IO Word16
forall (m :: * -> *) a. Monad m => a -> m a
return Word16
result

#if defined(ENABLE_OVERLOADING)
data RendererGetAlphaMethodInfo
instance (signature ~ (Pango.Enums.RenderPart -> m Word16), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererGetAlphaMethodInfo a signature where
    overloadedMethod = rendererGetAlpha

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


#endif

-- method Renderer::get_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "part"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "RenderPart" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the part to get the color for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "Color" })
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_get_color" pango_renderer_get_color :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    CUInt ->                                -- part : TInterface (Name {namespace = "Pango", name = "RenderPart"})
    IO (Ptr Pango.Color.Color)

-- | Gets the current rendering color for the specified part.
-- 
-- /Since: 1.8/
rendererGetColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Pango.Enums.RenderPart
    -- ^ /@part@/: the part to get the color for
    -> m (Maybe Pango.Color.Color)
    -- ^ __Returns:__ the color for the
    --   specified part, or 'P.Nothing' if it hasn\'t been set and should be
    --   inherited from the environment.
rendererGetColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> RenderPart -> m (Maybe Color)
rendererGetColor a
renderer RenderPart
part = IO (Maybe Color) -> m (Maybe Color)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Color) -> m (Maybe Color))
-> IO (Maybe Color) -> m (Maybe Color)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    let part' :: CUInt
part' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RenderPart -> Int) -> RenderPart -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderPart -> Int
forall a. Enum a => a -> Int
fromEnum) RenderPart
part
    Ptr Color
result <- Ptr Renderer -> CUInt -> IO (Ptr Color)
pango_renderer_get_color Ptr Renderer
renderer' CUInt
part'
    Maybe Color
maybeResult <- Ptr Color -> (Ptr Color -> IO Color) -> IO (Maybe Color)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Color
result ((Ptr Color -> IO Color) -> IO (Maybe Color))
-> (Ptr Color -> IO Color) -> IO (Maybe Color)
forall a b. (a -> b) -> a -> b
$ \Ptr Color
result' -> do
        Color
result'' <- ((ManagedPtr Color -> Color) -> Ptr Color -> IO Color
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Color -> Color
Pango.Color.Color) Ptr Color
result'
        Color -> IO Color
forall (m :: * -> *) a. Monad m => a -> m a
return Color
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Maybe Color -> IO (Maybe Color)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Color
maybeResult

#if defined(ENABLE_OVERLOADING)
data RendererGetColorMethodInfo
instance (signature ~ (Pango.Enums.RenderPart -> m (Maybe Pango.Color.Color)), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererGetColorMethodInfo a signature where
    overloadedMethod = rendererGetColor

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


#endif

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

foreign import ccall "pango_renderer_get_layout" pango_renderer_get_layout :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    IO (Ptr Pango.Layout.Layout)

-- | Gets the layout currently being rendered using /@renderer@/.
-- 
-- Calling this function only makes sense from inside a subclass\'s
-- methods, like in its draw_shape vfunc, for example.
-- 
-- The returned layout should not be modified while still being
-- rendered.
-- 
-- /Since: 1.20/
rendererGetLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> m (Maybe Pango.Layout.Layout)
    -- ^ __Returns:__ the layout, or 'P.Nothing' if
    --   no layout is being rendered using /@renderer@/ at this time.
rendererGetLayout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> m (Maybe Layout)
rendererGetLayout a
renderer = IO (Maybe Layout) -> m (Maybe Layout)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Layout) -> m (Maybe Layout))
-> IO (Maybe Layout) -> m (Maybe Layout)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Layout
result <- Ptr Renderer -> IO (Ptr Layout)
pango_renderer_get_layout Ptr Renderer
renderer'
    Maybe Layout
maybeResult <- Ptr Layout -> (Ptr Layout -> IO Layout) -> IO (Maybe Layout)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Layout
result ((Ptr Layout -> IO Layout) -> IO (Maybe Layout))
-> (Ptr Layout -> IO Layout) -> IO (Maybe Layout)
forall a b. (a -> b) -> a -> b
$ \Ptr Layout
result' -> do
        Layout
result'' <- ((ManagedPtr Layout -> Layout) -> Ptr Layout -> IO Layout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Layout -> Layout
Pango.Layout.Layout) Ptr Layout
result'
        Layout -> IO Layout
forall (m :: * -> *) a. Monad m => a -> m a
return Layout
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Maybe Layout -> IO (Maybe Layout)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Layout
maybeResult

#if defined(ENABLE_OVERLOADING)
data RendererGetLayoutMethodInfo
instance (signature ~ (m (Maybe Pango.Layout.Layout)), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererGetLayoutMethodInfo a signature where
    overloadedMethod = rendererGetLayout

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


#endif

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

foreign import ccall "pango_renderer_get_layout_line" pango_renderer_get_layout_line :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    IO (Ptr Pango.LayoutLine.LayoutLine)

-- | Gets the layout line currently being rendered using /@renderer@/.
-- 
-- Calling this function only makes sense from inside a subclass\'s
-- methods, like in its draw_shape vfunc, for example.
-- 
-- The returned layout line should not be modified while still being
-- rendered.
-- 
-- /Since: 1.20/
rendererGetLayoutLine ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> m (Maybe Pango.LayoutLine.LayoutLine)
    -- ^ __Returns:__ the layout line, or 'P.Nothing'
    --   if no layout line is being rendered using /@renderer@/ at this time.
rendererGetLayoutLine :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> m (Maybe LayoutLine)
rendererGetLayoutLine a
renderer = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr LayoutLine
result <- Ptr Renderer -> IO (Ptr LayoutLine)
pango_renderer_get_layout_line Ptr Renderer
renderer'
    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
renderer
    Maybe LayoutLine -> IO (Maybe LayoutLine)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe LayoutLine
maybeResult

#if defined(ENABLE_OVERLOADING)
data RendererGetLayoutLineMethodInfo
instance (signature ~ (m (Maybe Pango.LayoutLine.LayoutLine)), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererGetLayoutLineMethodInfo a signature where
    overloadedMethod = rendererGetLayoutLine

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


#endif

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

foreign import ccall "pango_renderer_get_matrix" pango_renderer_get_matrix :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    IO (Ptr Pango.Matrix.Matrix)

-- | Gets the transformation matrix that will be applied when
-- rendering.
-- 
-- See 'GI.Pango.Objects.Renderer.rendererSetMatrix'.
-- 
-- /Since: 1.8/
rendererGetMatrix ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> m (Maybe Pango.Matrix.Matrix)
    -- ^ __Returns:__ the matrix, or 'P.Nothing' if no matrix has
    --   been set (which is the same as the identity matrix). The returned
    --   matrix is owned by Pango and must not be modified or freed.
rendererGetMatrix :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> m (Maybe Matrix)
rendererGetMatrix a
renderer = IO (Maybe Matrix) -> m (Maybe Matrix)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Matrix) -> m (Maybe Matrix))
-> IO (Maybe Matrix) -> m (Maybe Matrix)
forall a b. (a -> b) -> a -> b
$ do
    Ptr Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Matrix
result <- Ptr Renderer -> IO (Ptr Matrix)
pango_renderer_get_matrix Ptr Renderer
renderer'
    Maybe Matrix
maybeResult <- Ptr Matrix -> (Ptr Matrix -> IO Matrix) -> IO (Maybe Matrix)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Matrix
result ((Ptr Matrix -> IO Matrix) -> IO (Maybe Matrix))
-> (Ptr Matrix -> IO Matrix) -> IO (Maybe Matrix)
forall a b. (a -> b) -> a -> b
$ \Ptr Matrix
result' -> do
        Matrix
result'' <- ((ManagedPtr Matrix -> Matrix) -> Ptr Matrix -> IO Matrix
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Matrix -> Matrix
Pango.Matrix.Matrix) Ptr Matrix
result'
        Matrix -> IO Matrix
forall (m :: * -> *) a. Monad m => a -> m a
return Matrix
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Maybe Matrix -> IO (Maybe Matrix)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Matrix
maybeResult

#if defined(ENABLE_OVERLOADING)
data RendererGetMatrixMethodInfo
instance (signature ~ (m (Maybe Pango.Matrix.Matrix)), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererGetMatrixMethodInfo a signature where
    overloadedMethod = rendererGetMatrix

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


#endif

-- method Renderer::part_changed
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "part"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "RenderPart" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the part for which rendering has changed."
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_part_changed" pango_renderer_part_changed :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    CUInt ->                                -- part : TInterface (Name {namespace = "Pango", name = "RenderPart"})
    IO ()

-- | Informs Pango that the way that the rendering is done
-- for /@part@/ has changed.
-- 
-- This should be called if the rendering changes in a way that would
-- prevent multiple pieces being joined together into one drawing call.
-- For instance, if a subclass of @PangoRenderer@ was to add a stipple
-- option for drawing underlines, it needs to call
-- 
-- >pango_renderer_part_changed (render, PANGO_RENDER_PART_UNDERLINE);
-- 
-- 
-- When the stipple changes or underlines with different stipples
-- might be joined together. Pango automatically calls this for
-- changes to colors. (See 'GI.Pango.Objects.Renderer.rendererSetColor')
-- 
-- /Since: 1.8/
rendererPartChanged ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Pango.Enums.RenderPart
    -- ^ /@part@/: the part for which rendering has changed.
    -> m ()
rendererPartChanged :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> RenderPart -> m ()
rendererPartChanged a
renderer RenderPart
part = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    let part' :: CUInt
part' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RenderPart -> Int) -> RenderPart -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderPart -> Int
forall a. Enum a => a -> Int
fromEnum) RenderPart
part
    Ptr Renderer -> CUInt -> IO ()
pango_renderer_part_changed Ptr Renderer
renderer' CUInt
part'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererPartChangedMethodInfo
instance (signature ~ (Pango.Enums.RenderPart -> m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererPartChangedMethodInfo a signature where
    overloadedMethod = rendererPartChanged

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


#endif

-- method Renderer::set_alpha
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "part"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "RenderPart" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the part to set the alpha for"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "alpha"
--           , argType = TBasicType TUInt16
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "an alpha value between 1 and 65536, or 0 to unset the alpha"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_set_alpha" pango_renderer_set_alpha :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    CUInt ->                                -- part : TInterface (Name {namespace = "Pango", name = "RenderPart"})
    Word16 ->                               -- alpha : TBasicType TUInt16
    IO ()

-- | Sets the alpha for part of the rendering.
-- 
-- Note that the alpha may only be used if a color is
-- specified for /@part@/ as well.
-- 
-- /Since: 1.38/
rendererSetAlpha ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Pango.Enums.RenderPart
    -- ^ /@part@/: the part to set the alpha for
    -> Word16
    -- ^ /@alpha@/: an alpha value between 1 and 65536, or 0 to unset the alpha
    -> m ()
rendererSetAlpha :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> RenderPart -> Word16 -> m ()
rendererSetAlpha a
renderer RenderPart
part Word16
alpha = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    let part' :: CUInt
part' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RenderPart -> Int) -> RenderPart -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderPart -> Int
forall a. Enum a => a -> Int
fromEnum) RenderPart
part
    Ptr Renderer -> CUInt -> Word16 -> IO ()
pango_renderer_set_alpha Ptr Renderer
renderer' CUInt
part' Word16
alpha
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererSetAlphaMethodInfo
instance (signature ~ (Pango.Enums.RenderPart -> Word16 -> m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererSetAlphaMethodInfo a signature where
    overloadedMethod = rendererSetAlpha

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


#endif

-- method Renderer::set_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "part"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "RenderPart" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the part to change the color of"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "color"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Color" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the new color or %NULL to unset the current color"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_set_color" pango_renderer_set_color :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    CUInt ->                                -- part : TInterface (Name {namespace = "Pango", name = "RenderPart"})
    Ptr Pango.Color.Color ->                -- color : TInterface (Name {namespace = "Pango", name = "Color"})
    IO ()

-- | Sets the color for part of the rendering.
-- 
-- Also see 'GI.Pango.Objects.Renderer.rendererSetAlpha'.
-- 
-- /Since: 1.8/
rendererSetColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Pango.Enums.RenderPart
    -- ^ /@part@/: the part to change the color of
    -> Maybe (Pango.Color.Color)
    -- ^ /@color@/: the new color or 'P.Nothing' to unset the current color
    -> m ()
rendererSetColor :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> RenderPart -> Maybe Color -> m ()
rendererSetColor a
renderer RenderPart
part Maybe Color
color = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    let part' :: CUInt
part' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (RenderPart -> Int) -> RenderPart -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RenderPart -> Int
forall a. Enum a => a -> Int
fromEnum) RenderPart
part
    Ptr Color
maybeColor <- case Maybe Color
color of
        Maybe Color
Nothing -> Ptr Color -> IO (Ptr Color)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Color
forall a. Ptr a
nullPtr
        Just Color
jColor -> do
            Ptr Color
jColor' <- Color -> IO (Ptr Color)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Color
jColor
            Ptr Color -> IO (Ptr Color)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Color
jColor'
    Ptr Renderer -> CUInt -> Ptr Color -> IO ()
pango_renderer_set_color Ptr Renderer
renderer' CUInt
part' Ptr Color
maybeColor
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Maybe Color -> (Color -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Color
color Color -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererSetColorMethodInfo
instance (signature ~ (Pango.Enums.RenderPart -> Maybe (Pango.Color.Color) -> m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererSetColorMethodInfo a signature where
    overloadedMethod = rendererSetColor

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


#endif

-- method Renderer::set_matrix
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "renderer"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Renderer" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `PangoRenderer`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "matrix"
--           , argType =
--               TInterface Name { namespace = "Pango" , name = "Matrix" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "a `PangoMatrix`, or %NULL to unset any existing matrix\n (No matrix set is the same as setting the identity matrix.)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "pango_renderer_set_matrix" pango_renderer_set_matrix :: 
    Ptr Renderer ->                         -- renderer : TInterface (Name {namespace = "Pango", name = "Renderer"})
    Ptr Pango.Matrix.Matrix ->              -- matrix : TInterface (Name {namespace = "Pango", name = "Matrix"})
    IO ()

-- | Sets the transformation matrix that will be applied when rendering.
-- 
-- /Since: 1.8/
rendererSetMatrix ::
    (B.CallStack.HasCallStack, MonadIO m, IsRenderer a) =>
    a
    -- ^ /@renderer@/: a @PangoRenderer@
    -> Maybe (Pango.Matrix.Matrix)
    -- ^ /@matrix@/: a @PangoMatrix@, or 'P.Nothing' to unset any existing matrix
    --  (No matrix set is the same as setting the identity matrix.)
    -> m ()
rendererSetMatrix :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsRenderer a) =>
a -> Maybe Matrix -> m ()
rendererSetMatrix a
renderer Maybe Matrix
matrix = 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 Renderer
renderer' <- a -> IO (Ptr Renderer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
renderer
    Ptr Matrix
maybeMatrix <- case Maybe Matrix
matrix of
        Maybe Matrix
Nothing -> Ptr Matrix -> IO (Ptr Matrix)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Matrix
forall a. Ptr a
nullPtr
        Just Matrix
jMatrix -> do
            Ptr Matrix
jMatrix' <- Matrix -> IO (Ptr Matrix)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Matrix
jMatrix
            Ptr Matrix -> IO (Ptr Matrix)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Matrix
jMatrix'
    Ptr Renderer -> Ptr Matrix -> IO ()
pango_renderer_set_matrix Ptr Renderer
renderer' Ptr Matrix
maybeMatrix
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
renderer
    Maybe Matrix -> (Matrix -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe Matrix
matrix Matrix -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data RendererSetMatrixMethodInfo
instance (signature ~ (Maybe (Pango.Matrix.Matrix) -> m ()), MonadIO m, IsRenderer a) => O.OverloadedMethod RendererSetMatrixMethodInfo a signature where
    overloadedMethod = rendererSetMatrix

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


#endif