{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.PrintContext
(
PrintContext(..) ,
IsPrintContext ,
toPrintContext ,
noPrintContext ,
#if defined(ENABLE_OVERLOADING)
ResolvePrintContextMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PrintContextCreatePangoContextMethodInfo,
#endif
printContextCreatePangoContext ,
#if defined(ENABLE_OVERLOADING)
PrintContextCreatePangoLayoutMethodInfo ,
#endif
printContextCreatePangoLayout ,
#if defined(ENABLE_OVERLOADING)
PrintContextGetCairoContextMethodInfo ,
#endif
printContextGetCairoContext ,
#if defined(ENABLE_OVERLOADING)
PrintContextGetDpiXMethodInfo ,
#endif
printContextGetDpiX ,
#if defined(ENABLE_OVERLOADING)
PrintContextGetDpiYMethodInfo ,
#endif
printContextGetDpiY ,
#if defined(ENABLE_OVERLOADING)
PrintContextGetHardMarginsMethodInfo ,
#endif
printContextGetHardMargins ,
#if defined(ENABLE_OVERLOADING)
PrintContextGetHeightMethodInfo ,
#endif
printContextGetHeight ,
#if defined(ENABLE_OVERLOADING)
PrintContextGetPageSetupMethodInfo ,
#endif
printContextGetPageSetup ,
#if defined(ENABLE_OVERLOADING)
PrintContextGetPangoFontmapMethodInfo ,
#endif
printContextGetPangoFontmap ,
#if defined(ENABLE_OVERLOADING)
PrintContextGetWidthMethodInfo ,
#endif
printContextGetWidth ,
#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.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.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
newtype PrintContext = PrintContext (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)
foreign import ccall "gtk_print_context_get_type"
c_gtk_print_context_get_type :: IO GType
instance GObject PrintContext where
gobjectType :: IO GType
gobjectType = IO GType
c_gtk_print_context_get_type
instance B.GValue.IsGValue PrintContext where
toGValue :: PrintContext -> IO GValue
toGValue o :: PrintContext
o = do
GType
gtype <- IO GType
c_gtk_print_context_get_type
PrintContext -> (Ptr PrintContext -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PrintContext
o (GType
-> (GValue -> Ptr PrintContext -> IO ())
-> Ptr PrintContext
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr PrintContext -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
fromGValue :: GValue -> IO PrintContext
fromGValue gv :: GValue
gv = do
Ptr PrintContext
ptr <- GValue -> IO (Ptr PrintContext)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr PrintContext)
(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
class (GObject o, O.IsDescendantOf PrintContext o) => IsPrintContext o
instance (GObject o, O.IsDescendantOf PrintContext o) => IsPrintContext o
instance O.HasParentTypes PrintContext
type instance O.ParentTypes PrintContext = '[GObject.Object.Object]
toPrintContext :: (MonadIO m, IsPrintContext o) => o -> m PrintContext
toPrintContext :: o -> m PrintContext
toPrintContext = IO PrintContext -> m PrintContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr PrintContext -> PrintContext
PrintContext
noPrintContext :: Maybe PrintContext
noPrintContext :: Maybe PrintContext
noPrintContext = Maybe PrintContext
forall a. Maybe a
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.MethodInfo 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
#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
foreign import ccall "gtk_print_context_create_pango_context" gtk_print_context_create_pango_context ::
Ptr PrintContext ->
IO (Ptr Pango.Context.Context)
printContextCreatePangoContext ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m Pango.Context.Context
printContextCreatePangoContext :: a -> m Context
printContextCreatePangoContext context :: 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 "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.MethodInfo PrintContextCreatePangoContextMethodInfo a signature where
overloadedMethod = printContextCreatePangoContext
#endif
foreign import ccall "gtk_print_context_create_pango_layout" gtk_print_context_create_pango_layout ::
Ptr PrintContext ->
IO (Ptr Pango.Layout.Layout)
printContextCreatePangoLayout ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m Pango.Layout.Layout
printContextCreatePangoLayout :: a -> m Layout
printContextCreatePangoLayout context :: 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 "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.MethodInfo PrintContextCreatePangoLayoutMethodInfo a signature where
overloadedMethod = printContextCreatePangoLayout
#endif
foreign import ccall "gtk_print_context_get_cairo_context" gtk_print_context_get_cairo_context ::
Ptr PrintContext ->
IO (Ptr Cairo.Context.Context)
printContextGetCairoContext ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m Cairo.Context.Context
printContextGetCairoContext :: a -> m Context
printContextGetCairoContext context :: 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 "printContextGetCairoContext" Ptr Context
result
Context
result' <- ((ManagedPtr Context -> Context) -> Ptr Context -> IO Context
forall a.
(HasCallStack, BoxedObject 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.MethodInfo PrintContextGetCairoContextMethodInfo a signature where
overloadedMethod = printContextGetCairoContext
#endif
foreign import ccall "gtk_print_context_get_dpi_x" gtk_print_context_get_dpi_x ::
Ptr PrintContext ->
IO CDouble
printContextGetDpiX ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m Double
printContextGetDpiX :: a -> m Double
printContextGetDpiX context :: 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.MethodInfo PrintContextGetDpiXMethodInfo a signature where
overloadedMethod = printContextGetDpiX
#endif
foreign import ccall "gtk_print_context_get_dpi_y" gtk_print_context_get_dpi_y ::
Ptr PrintContext ->
IO CDouble
printContextGetDpiY ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m Double
printContextGetDpiY :: a -> m Double
printContextGetDpiY context :: 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.MethodInfo PrintContextGetDpiYMethodInfo a signature where
overloadedMethod = printContextGetDpiY
#endif
foreign import ccall "gtk_print_context_get_hard_margins" gtk_print_context_get_hard_margins ::
Ptr PrintContext ->
Ptr CDouble ->
Ptr CDouble ->
Ptr CDouble ->
Ptr CDouble ->
IO CInt
printContextGetHardMargins ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m ((Bool, Double, Double, Double, Double))
printContextGetHardMargins :: a -> m (Bool, Double, Double, Double, Double)
printContextGetHardMargins context :: 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
/= 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.MethodInfo PrintContextGetHardMarginsMethodInfo a signature where
overloadedMethod = printContextGetHardMargins
#endif
foreign import ccall "gtk_print_context_get_height" gtk_print_context_get_height ::
Ptr PrintContext ->
IO CDouble
printContextGetHeight ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m Double
printContextGetHeight :: a -> m Double
printContextGetHeight context :: 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.MethodInfo PrintContextGetHeightMethodInfo a signature where
overloadedMethod = printContextGetHeight
#endif
foreign import ccall "gtk_print_context_get_page_setup" gtk_print_context_get_page_setup ::
Ptr PrintContext ->
IO (Ptr Gtk.PageSetup.PageSetup)
printContextGetPageSetup ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m Gtk.PageSetup.PageSetup
printContextGetPageSetup :: a -> m PageSetup
printContextGetPageSetup context :: 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 "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.MethodInfo PrintContextGetPageSetupMethodInfo a signature where
overloadedMethod = printContextGetPageSetup
#endif
foreign import ccall "gtk_print_context_get_pango_fontmap" gtk_print_context_get_pango_fontmap ::
Ptr PrintContext ->
IO (Ptr Pango.FontMap.FontMap)
printContextGetPangoFontmap ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m Pango.FontMap.FontMap
printContextGetPangoFontmap :: a -> m FontMap
printContextGetPangoFontmap context :: 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 "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.MethodInfo PrintContextGetPangoFontmapMethodInfo a signature where
overloadedMethod = printContextGetPangoFontmap
#endif
foreign import ccall "gtk_print_context_get_width" gtk_print_context_get_width ::
Ptr PrintContext ->
IO CDouble
printContextGetWidth ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> m Double
printContextGetWidth :: a -> m Double
printContextGetWidth context :: 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.MethodInfo PrintContextGetWidthMethodInfo a signature where
overloadedMethod = printContextGetWidth
#endif
foreign import ccall "gtk_print_context_set_cairo_context" gtk_print_context_set_cairo_context ::
Ptr PrintContext ->
Ptr Cairo.Context.Context ->
CDouble ->
CDouble ->
IO ()
printContextSetCairoContext ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintContext a) =>
a
-> Cairo.Context.Context
-> Double
-> Double
-> m ()
printContextSetCairoContext :: a -> Context -> Double -> Double -> m ()
printContextSetCairoContext context :: a
context cr :: Context
cr dpiX :: Double
dpiX dpiY :: 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.MethodInfo PrintContextSetCairoContextMethodInfo a signature where
overloadedMethod = printContextSetCairoContext
#endif