{-# 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 ,
#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.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.GHashTable as B.GHT
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.Kind as DK
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 Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Structs.PaperSize as Gtk.PaperSize
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
#else
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
#endif
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
$c== :: PrintContext -> PrintContext -> Bool
== :: PrintContext -> PrintContext -> Bool
$c/= :: PrintContext -> PrintContext -> Bool
/= :: 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
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]
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 a. IO a -> m a
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
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 <- 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 /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject PrintContext ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolvePrintContextMethod (t :: Symbol) (o :: DK.Type) :: DK.Type 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, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PrintContext = PrintContextSignalList
type PrintContextSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Context
printContextCreatePangoContext a
context = IO Context -> m Context
forall a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_print_context_create_pango_context context'
checkUnexpectedReturnNULL "printContextCreatePangoContext" result
result' <- (wrapObject Pango.Context.Context) result
touchManagedPtr context
return 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextCreatePangoContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Layout
printContextCreatePangoLayout a
context = IO Layout -> m Layout
forall a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_print_context_create_pango_layout context'
checkUnexpectedReturnNULL "printContextCreatePangoLayout" result
result' <- (wrapObject Pango.Layout.Layout) result
touchManagedPtr context
return 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextCreatePangoLayout",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Context
printContextGetCairoContext a
context = IO Context -> m Context
forall a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_print_context_get_cairo_context context'
checkUnexpectedReturnNULL "printContextGetCairoContext" result
result' <- (newBoxed Cairo.Context.Context) result
touchManagedPtr context
return 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextGetCairoContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Double
printContextGetDpiX a
context = IO Double -> m Double
forall a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_print_context_get_dpi_x context'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr context
return 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextGetDpiX",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Double
printContextGetDpiY a
context = IO Double -> m Double
forall a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_print_context_get_dpi_y context'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr context
return 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextGetDpiY",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: 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 a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
top <- allocMem :: IO (Ptr CDouble)
bottom <- allocMem :: IO (Ptr CDouble)
left <- allocMem :: IO (Ptr CDouble)
right <- allocMem :: IO (Ptr CDouble)
result <- gtk_print_context_get_hard_margins context' top bottom left right
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
top' <- peek top
let top'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
top'
bottom' <- peek bottom
let bottom'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
bottom'
left' <- peek left
let left'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
left'
right' <- peek right
let right'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
right'
touchManagedPtr context
freeMem top
freeMem bottom
freeMem left
freeMem right
return (result', top'', bottom'', left'', 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextGetHardMargins",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Double
printContextGetHeight a
context = IO Double -> m Double
forall a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_print_context_get_height context'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr context
return 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextGetHeight",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m PageSetup
printContextGetPageSetup a
context = IO PageSetup -> m PageSetup
forall a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_print_context_get_page_setup context'
checkUnexpectedReturnNULL "printContextGetPageSetup" result
result' <- (newObject Gtk.PageSetup.PageSetup) result
touchManagedPtr context
return 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextGetPageSetup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m FontMap
printContextGetPangoFontmap a
context = IO FontMap -> m FontMap
forall a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_print_context_get_pango_fontmap context'
checkUnexpectedReturnNULL "printContextGetPangoFontmap" result
result' <- (newObject Pango.FontMap.FontMap) result
touchManagedPtr context
return 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextGetPangoFontmap",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintContext a) =>
a -> m Double
printContextGetWidth a
context = IO Double -> m Double
forall a. IO a -> m a
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
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
result <- gtk_print_context_get_width context'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr context
return 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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextGetWidth",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v: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 :: 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 a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
context' <- a -> IO (Ptr PrintContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
cr' <- unsafeManagedPtrGetPtr cr
let dpiX' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
dpiX
let dpiY' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
dpiY
gtk_print_context_set_cairo_context context' cr' dpiX' dpiY'
touchManagedPtr context
touchManagedPtr cr
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 = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.PrintContext.printContextSetCairoContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-PrintContext.html#v:printContextSetCairoContext"
})
#endif