{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A GtkPrintContext encapsulates context information that is required when
-- drawing pages for printing, such as the cairo context and important
-- parameters like page size and resolution. It also lets you easily
-- create t'GI.Pango.Objects.Layout.Layout' and t'GI.Pango.Objects.Context.Context' objects that match the font metrics
-- of the cairo surface.
-- 
-- GtkPrintContext objects gets passed to the [beginPrint]("GI.Gtk.Objects.PrintOperation#g:signal:beginPrint"),
-- [endPrint]("GI.Gtk.Objects.PrintOperation#g:signal:endPrint"), [requestPageSetup]("GI.Gtk.Objects.PrintOperation#g:signal:requestPageSetup") and
-- [drawPage]("GI.Gtk.Objects.PrintOperation#g:signal:drawPage") signals on the t'GI.Gtk.Objects.PrintOperation.PrintOperation'.
-- 
-- ## Using GtkPrintContext in a [drawPage]("GI.Gtk.Objects.PrintOperation#g:signal:drawPage") callback
-- 
-- 
-- === /C code/
-- >
-- >static void
-- >draw_page (GtkPrintOperation *operation,
-- >	   GtkPrintContext   *context,
-- >	   int                page_nr)
-- >{
-- >  cairo_t *cr;
-- >  PangoLayout *layout;
-- >  PangoFontDescription *desc;
-- >
-- >  cr = gtk_print_context_get_cairo_context (context);
-- >
-- >  // Draw a red rectangle, as wide as the paper (inside the margins)
-- >  cairo_set_source_rgb (cr, 1.0, 0, 0);
-- >  cairo_rectangle (cr, 0, 0, gtk_print_context_get_width (context), 50);
-- >
-- >  cairo_fill (cr);
-- >
-- >  // Draw some lines
-- >  cairo_move_to (cr, 20, 10);
-- >  cairo_line_to (cr, 40, 20);
-- >  cairo_arc (cr, 60, 60, 20, 0, M_PI);
-- >  cairo_line_to (cr, 80, 20);
-- >
-- >  cairo_set_source_rgb (cr, 0, 0, 0);
-- >  cairo_set_line_width (cr, 5);
-- >  cairo_set_line_cap (cr, CAIRO_LINE_CAP_ROUND);
-- >  cairo_set_line_join (cr, CAIRO_LINE_JOIN_ROUND);
-- >
-- >  cairo_stroke (cr);
-- >
-- >  // Draw some text
-- >  layout = gtk_print_context_create_pango_layout (context);
-- >  pango_layout_set_text (layout, "Hello World! Printing is easy", -1);
-- >  desc = pango_font_description_from_string ("sans 28");
-- >  pango_layout_set_font_description (layout, desc);
-- >  pango_font_description_free (desc);
-- >
-- >  cairo_move_to (cr, 30, 20);
-- >  pango_cairo_layout_path (cr, layout);
-- >
-- >  // Font Outline
-- >  cairo_set_source_rgb (cr, 0.93, 1.0, 0.47);
-- >  cairo_set_line_width (cr, 0.5);
-- >  cairo_stroke_preserve (cr);
-- >
-- >  // Font Fill
-- >  cairo_set_source_rgb (cr, 0, 0.0, 1.0);
-- >  cairo_fill (cr);
-- >
-- >  g_object_unref (layout);
-- >}
-- 

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

module GI.Gtk.Objects.PrintContext
    ( 

-- * Exported types
    PrintContext(..)                        ,
    IsPrintContext                          ,
    toPrintContext                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [createPangoContext]("GI.Gtk.Objects.PrintContext#g:method:createPangoContext"), [createPangoLayout]("GI.Gtk.Objects.PrintContext#g:method:createPangoLayout"), [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"), [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
-- [getCairoContext]("GI.Gtk.Objects.PrintContext#g:method:getCairoContext"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDpiX]("GI.Gtk.Objects.PrintContext#g:method:getDpiX"), [getDpiY]("GI.Gtk.Objects.PrintContext#g:method:getDpiY"), [getHardMargins]("GI.Gtk.Objects.PrintContext#g:method:getHardMargins"), [getHeight]("GI.Gtk.Objects.PrintContext#g:method:getHeight"), [getPageSetup]("GI.Gtk.Objects.PrintContext#g:method:getPageSetup"), [getPangoFontmap]("GI.Gtk.Objects.PrintContext#g:method:getPangoFontmap"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getWidth]("GI.Gtk.Objects.PrintContext#g:method:getWidth").
-- 
-- ==== Setters
-- [setCairoContext]("GI.Gtk.Objects.PrintContext#g:method:setCairoContext"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolvePrintContextMethod               ,
#endif

-- ** createPangoContext #method:createPangoContext#

#if defined(ENABLE_OVERLOADING)
    PrintContextCreatePangoContextMethodInfo,
#endif
    printContextCreatePangoContext          ,


-- ** createPangoLayout #method:createPangoLayout#

#if defined(ENABLE_OVERLOADING)
    PrintContextCreatePangoLayoutMethodInfo ,
#endif
    printContextCreatePangoLayout           ,


-- ** getCairoContext #method:getCairoContext#

#if defined(ENABLE_OVERLOADING)
    PrintContextGetCairoContextMethodInfo   ,
#endif
    printContextGetCairoContext             ,


-- ** getDpiX #method:getDpiX#

#if defined(ENABLE_OVERLOADING)
    PrintContextGetDpiXMethodInfo           ,
#endif
    printContextGetDpiX                     ,


-- ** getDpiY #method:getDpiY#

#if defined(ENABLE_OVERLOADING)
    PrintContextGetDpiYMethodInfo           ,
#endif
    printContextGetDpiY                     ,


-- ** getHardMargins #method:getHardMargins#

#if defined(ENABLE_OVERLOADING)
    PrintContextGetHardMarginsMethodInfo    ,
#endif
    printContextGetHardMargins              ,


-- ** getHeight #method:getHeight#

#if defined(ENABLE_OVERLOADING)
    PrintContextGetHeightMethodInfo         ,
#endif
    printContextGetHeight                   ,


-- ** getPageSetup #method:getPageSetup#

#if defined(ENABLE_OVERLOADING)
    PrintContextGetPageSetupMethodInfo      ,
#endif
    printContextGetPageSetup                ,


-- ** getPangoFontmap #method:getPangoFontmap#

#if defined(ENABLE_OVERLOADING)
    PrintContextGetPangoFontmapMethodInfo   ,
#endif
    printContextGetPangoFontmap             ,


-- ** getWidth #method:getWidth#

#if defined(ENABLE_OVERLOADING)
    PrintContextGetWidthMethodInfo          ,
#endif
    printContextGetWidth                    ,


-- ** setCairoContext #method:setCairoContext#

#if defined(ENABLE_OVERLOADING)
    PrintContextSetCairoContextMethodInfo   ,
#endif
    printContextSetCairoContext             ,




    ) 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.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.Cairo.Structs.Context as Cairo.Context
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout

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

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

foreign import ccall "gtk_print_context_get_type"
    c_gtk_print_context_get_type :: IO B.Types.GType

instance B.Types.TypedObject PrintContext where
    glibType :: IO GType
glibType = IO GType
c_gtk_print_context_get_type

instance B.Types.GObject PrintContext

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

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

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

-- | Convert 'PrintContext' 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 PrintContext) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_print_context_get_type
    gvalueSet_ :: Ptr GValue -> Maybe PrintContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe PrintContext
P.Nothing = Ptr GValue -> Ptr PrintContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr PrintContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr PrintContext)
    gvalueSet_ Ptr GValue
gv (P.Just PrintContext
obj) = PrintContext -> (Ptr PrintContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PrintContext
obj (Ptr GValue -> Ptr PrintContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe PrintContext)
gvalueGet_ Ptr GValue
gv = do
        Ptr PrintContext
ptr <- Ptr GValue -> IO (Ptr PrintContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr PrintContext)
        if Ptr PrintContext
ptr Ptr PrintContext -> Ptr PrintContext -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr PrintContext
forall a. Ptr a
FP.nullPtr
        then PrintContext -> Maybe PrintContext
forall a. a -> Maybe a
P.Just (PrintContext -> Maybe PrintContext)
-> IO PrintContext -> IO (Maybe PrintContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr PrintContext -> PrintContext)
-> Ptr PrintContext -> IO PrintContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr PrintContext -> PrintContext
PrintContext Ptr PrintContext
ptr
        else Maybe PrintContext -> IO (Maybe PrintContext)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PrintContext
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolvePrintContextMethod (t :: Symbol) (o :: *) :: * where
    ResolvePrintContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePrintContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePrintContextMethod "createPangoContext" o = PrintContextCreatePangoContextMethodInfo
    ResolvePrintContextMethod "createPangoLayout" o = PrintContextCreatePangoLayoutMethodInfo
    ResolvePrintContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePrintContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePrintContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePrintContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePrintContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePrintContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePrintContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePrintContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePrintContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePrintContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePrintContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePrintContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePrintContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePrintContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePrintContextMethod "getCairoContext" o = PrintContextGetCairoContextMethodInfo
    ResolvePrintContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePrintContextMethod "getDpiX" o = PrintContextGetDpiXMethodInfo
    ResolvePrintContextMethod "getDpiY" o = PrintContextGetDpiYMethodInfo
    ResolvePrintContextMethod "getHardMargins" o = PrintContextGetHardMarginsMethodInfo
    ResolvePrintContextMethod "getHeight" o = PrintContextGetHeightMethodInfo
    ResolvePrintContextMethod "getPageSetup" o = PrintContextGetPageSetupMethodInfo
    ResolvePrintContextMethod "getPangoFontmap" o = PrintContextGetPangoFontmapMethodInfo
    ResolvePrintContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePrintContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePrintContextMethod "getWidth" o = PrintContextGetWidthMethodInfo
    ResolvePrintContextMethod "setCairoContext" o = PrintContextSetCairoContextMethodInfo
    ResolvePrintContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePrintContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePrintContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePrintContextMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePrintContextMethod t PrintContext, O.OverloadedMethod info PrintContext p) => OL.IsLabel t (PrintContext -> 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 ~ ResolvePrintContextMethod t PrintContext, O.OverloadedMethod info PrintContext p, R.HasField t PrintContext p) => R.HasField t PrintContext p where
    getField = O.overloadedMethod @info

#endif

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

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

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

-- | Creates a new t'GI.Pango.Objects.Context.Context' that can be used with the
-- t'GI.Gtk.Objects.PrintContext.PrintContext'.
printContextCreatePangoContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m Pango.Context.Context
    -- ^ __Returns:__ a new Pango context for /@context@/
printContextCreatePangoContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Context
printContextCreatePangoContext a
context = IO Context -> m Context
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Context -> m Context) -> IO Context -> m Context
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Context
result <- Ptr PrintContext -> IO (Ptr Context)
gtk_print_context_create_pango_context Ptr PrintContext
context'
    Text -> Ptr Context -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printContextCreatePangoContext" Ptr Context
result
    Context
result' <- ((ManagedPtr Context -> Context) -> Ptr Context -> IO Context
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Context -> Context
Pango.Context.Context) Ptr Context
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Context -> IO Context
forall (m :: * -> *) a. Monad m => a -> m a
return Context
result'

#if defined(ENABLE_OVERLOADING)
data PrintContextCreatePangoContextMethodInfo
instance (signature ~ (m Pango.Context.Context), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextCreatePangoContextMethodInfo a signature where
    overloadedMethod = printContextCreatePangoContext

instance O.OverloadedMethodInfo PrintContextCreatePangoContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextCreatePangoContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextCreatePangoContext"
        }


#endif

-- method PrintContext::create_pango_layout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintContext" , 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 "gtk_print_context_create_pango_layout" gtk_print_context_create_pango_layout :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    IO (Ptr Pango.Layout.Layout)

-- | Creates a new t'GI.Pango.Objects.Layout.Layout' that is suitable for use
-- with the t'GI.Gtk.Objects.PrintContext.PrintContext'.
printContextCreatePangoLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m Pango.Layout.Layout
    -- ^ __Returns:__ a new Pango layout for /@context@/
printContextCreatePangoLayout :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Layout
printContextCreatePangoLayout a
context = IO Layout -> m Layout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Layout -> m Layout) -> IO Layout -> m Layout
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Layout
result <- Ptr PrintContext -> IO (Ptr Layout)
gtk_print_context_create_pango_layout Ptr PrintContext
context'
    Text -> Ptr Layout -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printContextCreatePangoLayout" Ptr Layout
result
    Layout
result' <- ((ManagedPtr Layout -> Layout) -> Ptr Layout -> IO Layout
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr Layout -> Layout
Pango.Layout.Layout) Ptr Layout
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Layout -> IO Layout
forall (m :: * -> *) a. Monad m => a -> m a
return Layout
result'

#if defined(ENABLE_OVERLOADING)
data PrintContextCreatePangoLayoutMethodInfo
instance (signature ~ (m Pango.Layout.Layout), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextCreatePangoLayoutMethodInfo a signature where
    overloadedMethod = printContextCreatePangoLayout

instance O.OverloadedMethodInfo PrintContextCreatePangoLayoutMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextCreatePangoLayout",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextCreatePangoLayout"
        }


#endif

-- method PrintContext::get_cairo_context
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "cairo" , name = "Context" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_context_get_cairo_context" gtk_print_context_get_cairo_context :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    IO (Ptr Cairo.Context.Context)

-- | Obtains the cairo context that is associated with the
-- t'GI.Gtk.Objects.PrintContext.PrintContext'.
printContextGetCairoContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m Cairo.Context.Context
    -- ^ __Returns:__ the cairo context of /@context@/
printContextGetCairoContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Context
printContextGetCairoContext a
context = IO Context -> m Context
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Context -> m Context) -> IO Context -> m Context
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Context
result <- Ptr PrintContext -> IO (Ptr Context)
gtk_print_context_get_cairo_context Ptr PrintContext
context'
    Text -> Ptr Context -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printContextGetCairoContext" Ptr Context
result
    Context
result' <- ((ManagedPtr Context -> Context) -> Ptr Context -> IO Context
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Context -> Context
Cairo.Context.Context) Ptr Context
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Context -> IO Context
forall (m :: * -> *) a. Monad m => a -> m a
return Context
result'

#if defined(ENABLE_OVERLOADING)
data PrintContextGetCairoContextMethodInfo
instance (signature ~ (m Cairo.Context.Context), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextGetCairoContextMethodInfo a signature where
    overloadedMethod = printContextGetCairoContext

instance O.OverloadedMethodInfo PrintContextGetCairoContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextGetCairoContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextGetCairoContext"
        }


#endif

-- method PrintContext::get_dpi_x
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_context_get_dpi_x" gtk_print_context_get_dpi_x :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    IO CDouble

-- | Obtains the horizontal resolution of the t'GI.Gtk.Objects.PrintContext.PrintContext',
-- in dots per inch.
printContextGetDpiX ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m Double
    -- ^ __Returns:__ the horizontal resolution of /@context@/
printContextGetDpiX :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Double
printContextGetDpiX a
context = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CDouble
result <- Ptr PrintContext -> IO CDouble
gtk_print_context_get_dpi_x Ptr PrintContext
context'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PrintContextGetDpiXMethodInfo
instance (signature ~ (m Double), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextGetDpiXMethodInfo a signature where
    overloadedMethod = printContextGetDpiX

instance O.OverloadedMethodInfo PrintContextGetDpiXMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextGetDpiX",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextGetDpiX"
        }


#endif

-- method PrintContext::get_dpi_y
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_context_get_dpi_y" gtk_print_context_get_dpi_y :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    IO CDouble

-- | Obtains the vertical resolution of the t'GI.Gtk.Objects.PrintContext.PrintContext',
-- in dots per inch.
printContextGetDpiY ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m Double
    -- ^ __Returns:__ the vertical resolution of /@context@/
printContextGetDpiY :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Double
printContextGetDpiY a
context = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CDouble
result <- Ptr PrintContext -> IO CDouble
gtk_print_context_get_dpi_y Ptr PrintContext
context'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PrintContextGetDpiYMethodInfo
instance (signature ~ (m Double), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextGetDpiYMethodInfo a signature where
    overloadedMethod = printContextGetDpiY

instance O.OverloadedMethodInfo PrintContextGetDpiYMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextGetDpiY",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextGetDpiY"
        }


#endif

-- method PrintContext::get_hard_margins
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "top"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "top hardware printer margin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "bottom"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "bottom hardware printer margin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "left"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "left hardware printer margin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "right"
--           , argType = TBasicType TDouble
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "right hardware printer margin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_context_get_hard_margins" gtk_print_context_get_hard_margins :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    Ptr CDouble ->                          -- top : TBasicType TDouble
    Ptr CDouble ->                          -- bottom : TBasicType TDouble
    Ptr CDouble ->                          -- left : TBasicType TDouble
    Ptr CDouble ->                          -- right : TBasicType TDouble
    IO CInt

-- | Obtains the hardware printer margins of the t'GI.Gtk.Objects.PrintContext.PrintContext', in units.
printContextGetHardMargins ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m ((Bool, Double, Double, Double, Double))
    -- ^ __Returns:__ 'P.True' if the hard margins were retrieved
printContextGetHardMargins :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m (Bool, Double, Double, Double, Double)
printContextGetHardMargins a
context = IO (Bool, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Double, Double, Double, Double)
 -> m (Bool, Double, Double, Double, Double))
-> IO (Bool, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr CDouble
top <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
bottom <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
left <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    Ptr CDouble
right <- IO (Ptr CDouble)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr CDouble)
    CInt
result <- Ptr PrintContext
-> Ptr CDouble
-> Ptr CDouble
-> Ptr CDouble
-> Ptr CDouble
-> IO CInt
gtk_print_context_get_hard_margins Ptr PrintContext
context' Ptr CDouble
top Ptr CDouble
bottom Ptr CDouble
left Ptr CDouble
right
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    CDouble
top' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
top
    let top'' :: Double
top'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
top'
    CDouble
bottom' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
bottom
    let bottom'' :: Double
bottom'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
bottom'
    CDouble
left' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
left
    let left'' :: Double
left'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
left'
    CDouble
right' <- Ptr CDouble -> IO CDouble
forall a. Storable a => Ptr a -> IO a
peek Ptr CDouble
right
    let right'' :: Double
right'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
right'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
top
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
bottom
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
left
    Ptr CDouble -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr CDouble
right
    (Bool, Double, Double, Double, Double)
-> IO (Bool, Double, Double, Double, Double)
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool
result', Double
top'', Double
bottom'', Double
left'', Double
right'')

#if defined(ENABLE_OVERLOADING)
data PrintContextGetHardMarginsMethodInfo
instance (signature ~ (m ((Bool, Double, Double, Double, Double))), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextGetHardMarginsMethodInfo a signature where
    overloadedMethod = printContextGetHardMargins

instance O.OverloadedMethodInfo PrintContextGetHardMarginsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextGetHardMargins",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextGetHardMargins"
        }


#endif

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

foreign import ccall "gtk_print_context_get_height" gtk_print_context_get_height :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    IO CDouble

-- | Obtains the height of the t'GI.Gtk.Objects.PrintContext.PrintContext', in pixels.
printContextGetHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m Double
    -- ^ __Returns:__ the height of /@context@/
printContextGetHeight :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Double
printContextGetHeight a
context = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CDouble
result <- Ptr PrintContext -> IO CDouble
gtk_print_context_get_height Ptr PrintContext
context'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PrintContextGetHeightMethodInfo
instance (signature ~ (m Double), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextGetHeightMethodInfo a signature where
    overloadedMethod = printContextGetHeight

instance O.OverloadedMethodInfo PrintContextGetHeightMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextGetHeight",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextGetHeight"
        }


#endif

-- method PrintContext::get_page_setup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "PageSetup" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_context_get_page_setup" gtk_print_context_get_page_setup :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    IO (Ptr Gtk.PageSetup.PageSetup)

-- | Obtains the t'GI.Gtk.Objects.PageSetup.PageSetup' that determines the page
-- dimensions of the t'GI.Gtk.Objects.PrintContext.PrintContext'.
printContextGetPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m Gtk.PageSetup.PageSetup
    -- ^ __Returns:__ the page setup of /@context@/
printContextGetPageSetup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m PageSetup
printContextGetPageSetup a
context = IO PageSetup -> m PageSetup
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PageSetup -> m PageSetup) -> IO PageSetup -> m PageSetup
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr PageSetup
result <- Ptr PrintContext -> IO (Ptr PageSetup)
gtk_print_context_get_page_setup Ptr PrintContext
context'
    Text -> Ptr PageSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printContextGetPageSetup" Ptr PageSetup
result
    PageSetup
result' <- ((ManagedPtr PageSetup -> PageSetup)
-> Ptr PageSetup -> IO PageSetup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PageSetup -> PageSetup
Gtk.PageSetup.PageSetup) Ptr PageSetup
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    PageSetup -> IO PageSetup
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result'

#if defined(ENABLE_OVERLOADING)
data PrintContextGetPageSetupMethodInfo
instance (signature ~ (m Gtk.PageSetup.PageSetup), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextGetPageSetupMethodInfo a signature where
    overloadedMethod = printContextGetPageSetup

instance O.OverloadedMethodInfo PrintContextGetPageSetupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextGetPageSetup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextGetPageSetup"
        }


#endif

-- method PrintContext::get_pango_fontmap
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Pango" , name = "FontMap" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_context_get_pango_fontmap" gtk_print_context_get_pango_fontmap :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    IO (Ptr Pango.FontMap.FontMap)

-- | Returns a t'GI.Pango.Objects.FontMap.FontMap' that is suitable for use
-- with the t'GI.Gtk.Objects.PrintContext.PrintContext'.
printContextGetPangoFontmap ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m Pango.FontMap.FontMap
    -- ^ __Returns:__ the font map of /@context@/
printContextGetPangoFontmap :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m FontMap
printContextGetPangoFontmap a
context = IO FontMap -> m FontMap
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO FontMap -> m FontMap) -> IO FontMap -> m FontMap
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr FontMap
result <- Ptr PrintContext -> IO (Ptr FontMap)
gtk_print_context_get_pango_fontmap Ptr PrintContext
context'
    Text -> Ptr FontMap -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printContextGetPangoFontmap" Ptr FontMap
result
    FontMap
result' <- ((ManagedPtr FontMap -> FontMap) -> Ptr FontMap -> IO FontMap
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr FontMap -> FontMap
Pango.FontMap.FontMap) Ptr FontMap
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    FontMap -> IO FontMap
forall (m :: * -> *) a. Monad m => a -> m a
return FontMap
result'

#if defined(ENABLE_OVERLOADING)
data PrintContextGetPangoFontmapMethodInfo
instance (signature ~ (m Pango.FontMap.FontMap), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextGetPangoFontmapMethodInfo a signature where
    overloadedMethod = printContextGetPangoFontmap

instance O.OverloadedMethodInfo PrintContextGetPangoFontmapMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextGetPangoFontmap",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextGetPangoFontmap"
        }


#endif

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

foreign import ccall "gtk_print_context_get_width" gtk_print_context_get_width :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    IO CDouble

-- | Obtains the width of the t'GI.Gtk.Objects.PrintContext.PrintContext', in pixels.
printContextGetWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> m Double
    -- ^ __Returns:__ the width of /@context@/
printContextGetWidth :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Double
printContextGetWidth a
context = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CDouble
result <- Ptr PrintContext -> IO CDouble
gtk_print_context_get_width Ptr PrintContext
context'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PrintContextGetWidthMethodInfo
instance (signature ~ (m Double), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextGetWidthMethodInfo a signature where
    overloadedMethod = printContextGetWidth

instance O.OverloadedMethodInfo PrintContextGetWidthMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextGetWidth",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextGetWidth"
        }


#endif

-- method PrintContext::set_cairo_context
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintContext" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cr"
--           , argType =
--               TInterface Name { namespace = "cairo" , name = "Context" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the cairo context" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dpi_x"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the horizontal resolution to use with @cr"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dpi_y"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vertical resolution to use with @cr"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_context_set_cairo_context" gtk_print_context_set_cairo_context :: 
    Ptr PrintContext ->                     -- context : TInterface (Name {namespace = "Gtk", name = "PrintContext"})
    Ptr Cairo.Context.Context ->            -- cr : TInterface (Name {namespace = "cairo", name = "Context"})
    CDouble ->                              -- dpi_x : TBasicType TDouble
    CDouble ->                              -- dpi_y : TBasicType TDouble
    IO ()

-- | Sets a new cairo context on a print context.
-- 
-- This function is intended to be used when implementing
-- an internal print preview, it is not needed for printing,
-- since GTK itself creates a suitable cairo context in that
-- case.
printContextSetCairoContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
    a
    -- ^ /@context@/: a t'GI.Gtk.Objects.PrintContext.PrintContext'
    -> Cairo.Context.Context
    -- ^ /@cr@/: the cairo context
    -> Double
    -- ^ /@dpiX@/: the horizontal resolution to use with /@cr@/
    -> Double
    -- ^ /@dpiY@/: the vertical resolution to use with /@cr@/
    -> m ()
printContextSetCairoContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> Context -> Double -> Double -> m ()
printContextSetCairoContext a
context Context
cr Double
dpiX Double
dpiY = 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 PrintContext
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Context
cr' <- Context -> IO (Ptr Context)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Context
cr
    let dpiX' :: CDouble
dpiX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
dpiX
    let dpiY' :: CDouble
dpiY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
dpiY
    Ptr PrintContext -> Ptr Context -> CDouble -> CDouble -> IO ()
gtk_print_context_set_cairo_context Ptr PrintContext
context' Ptr Context
cr' CDouble
dpiX' CDouble
dpiY'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Context -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Context
cr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintContextSetCairoContextMethodInfo
instance (signature ~ (Cairo.Context.Context -> Double -> Double -> m ()), MonadIO m, IsPrintContext a) => O.OverloadedMethod PrintContextSetCairoContextMethodInfo a signature where
    overloadedMethod = printContextSetCairoContext

instance O.OverloadedMethodInfo PrintContextSetCairoContextMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintContext.printContextSetCairoContext",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintContext.html#v:printContextSetCairoContext"
        }


#endif