{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.PrintOperation
    ( 
    PrintOperation(..)                      ,
    IsPrintOperation                        ,
    toPrintOperation                        ,
 
#if defined(ENABLE_OVERLOADING)
    ResolvePrintOperationMethod             ,
#endif
#if defined(ENABLE_OVERLOADING)
    PrintOperationCancelMethodInfo          ,
#endif
    printOperationCancel                    ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationDrawPageFinishMethodInfo  ,
#endif
    printOperationDrawPageFinish            ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationGetDefaultPageSetupMethodInfo,
#endif
    printOperationGetDefaultPageSetup       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationGetEmbedPageSetupMethodInfo,
#endif
    printOperationGetEmbedPageSetup         ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationGetErrorMethodInfo        ,
#endif
    printOperationGetError                  ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationGetHasSelectionMethodInfo ,
#endif
    printOperationGetHasSelection           ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationGetNPagesToPrintMethodInfo,
#endif
    printOperationGetNPagesToPrint          ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationGetPrintSettingsMethodInfo,
#endif
    printOperationGetPrintSettings          ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationGetStatusMethodInfo       ,
#endif
    printOperationGetStatus                 ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationGetStatusStringMethodInfo ,
#endif
    printOperationGetStatusString           ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationGetSupportSelectionMethodInfo,
#endif
    printOperationGetSupportSelection       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationIsFinishedMethodInfo      ,
#endif
    printOperationIsFinished                ,
    printOperationNew                       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationRunMethodInfo             ,
#endif
    printOperationRun                       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetAllowAsyncMethodInfo   ,
#endif
    printOperationSetAllowAsync             ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetCurrentPageMethodInfo  ,
#endif
    printOperationSetCurrentPage            ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetCustomTabLabelMethodInfo,
#endif
    printOperationSetCustomTabLabel         ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetDefaultPageSetupMethodInfo,
#endif
    printOperationSetDefaultPageSetup       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetDeferDrawingMethodInfo ,
#endif
    printOperationSetDeferDrawing           ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetEmbedPageSetupMethodInfo,
#endif
    printOperationSetEmbedPageSetup         ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetExportFilenameMethodInfo,
#endif
    printOperationSetExportFilename         ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetHasSelectionMethodInfo ,
#endif
    printOperationSetHasSelection           ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetJobNameMethodInfo      ,
#endif
    printOperationSetJobName                ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetNPagesMethodInfo       ,
#endif
    printOperationSetNPages                 ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetPrintSettingsMethodInfo,
#endif
    printOperationSetPrintSettings          ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetShowProgressMethodInfo ,
#endif
    printOperationSetShowProgress           ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetSupportSelectionMethodInfo,
#endif
    printOperationSetSupportSelection       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetTrackPrintStatusMethodInfo,
#endif
    printOperationSetTrackPrintStatus       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetUnitMethodInfo         ,
#endif
    printOperationSetUnit                   ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationSetUseFullPageMethodInfo  ,
#endif
    printOperationSetUseFullPage            ,
 
#if defined(ENABLE_OVERLOADING)
    PrintOperationAllowAsyncPropertyInfo    ,
#endif
    constructPrintOperationAllowAsync       ,
    getPrintOperationAllowAsync             ,
#if defined(ENABLE_OVERLOADING)
    printOperationAllowAsync                ,
#endif
    setPrintOperationAllowAsync             ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationCurrentPagePropertyInfo   ,
#endif
    constructPrintOperationCurrentPage      ,
    getPrintOperationCurrentPage            ,
#if defined(ENABLE_OVERLOADING)
    printOperationCurrentPage               ,
#endif
    setPrintOperationCurrentPage            ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationCustomTabLabelPropertyInfo,
#endif
    clearPrintOperationCustomTabLabel       ,
    constructPrintOperationCustomTabLabel   ,
    getPrintOperationCustomTabLabel         ,
#if defined(ENABLE_OVERLOADING)
    printOperationCustomTabLabel            ,
#endif
    setPrintOperationCustomTabLabel         ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationDefaultPageSetupPropertyInfo,
#endif
    clearPrintOperationDefaultPageSetup     ,
    constructPrintOperationDefaultPageSetup ,
    getPrintOperationDefaultPageSetup       ,
#if defined(ENABLE_OVERLOADING)
    printOperationDefaultPageSetup          ,
#endif
    setPrintOperationDefaultPageSetup       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationEmbedPageSetupPropertyInfo,
#endif
    constructPrintOperationEmbedPageSetup   ,
    getPrintOperationEmbedPageSetup         ,
#if defined(ENABLE_OVERLOADING)
    printOperationEmbedPageSetup            ,
#endif
    setPrintOperationEmbedPageSetup         ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationExportFilenamePropertyInfo,
#endif
    clearPrintOperationExportFilename       ,
    constructPrintOperationExportFilename   ,
    getPrintOperationExportFilename         ,
#if defined(ENABLE_OVERLOADING)
    printOperationExportFilename            ,
#endif
    setPrintOperationExportFilename         ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationHasSelectionPropertyInfo  ,
#endif
    constructPrintOperationHasSelection     ,
    getPrintOperationHasSelection           ,
#if defined(ENABLE_OVERLOADING)
    printOperationHasSelection              ,
#endif
    setPrintOperationHasSelection           ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationJobNamePropertyInfo       ,
#endif
    constructPrintOperationJobName          ,
    getPrintOperationJobName                ,
#if defined(ENABLE_OVERLOADING)
    printOperationJobName                   ,
#endif
    setPrintOperationJobName                ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationNPagesPropertyInfo        ,
#endif
    constructPrintOperationNPages           ,
    getPrintOperationNPages                 ,
#if defined(ENABLE_OVERLOADING)
    printOperationNPages                    ,
#endif
    setPrintOperationNPages                 ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationNPagesToPrintPropertyInfo ,
#endif
    getPrintOperationNPagesToPrint          ,
#if defined(ENABLE_OVERLOADING)
    printOperationNPagesToPrint             ,
#endif
#if defined(ENABLE_OVERLOADING)
    PrintOperationPrintSettingsPropertyInfo ,
#endif
    clearPrintOperationPrintSettings        ,
    constructPrintOperationPrintSettings    ,
    getPrintOperationPrintSettings          ,
#if defined(ENABLE_OVERLOADING)
    printOperationPrintSettings             ,
#endif
    setPrintOperationPrintSettings          ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationShowProgressPropertyInfo  ,
#endif
    constructPrintOperationShowProgress     ,
    getPrintOperationShowProgress           ,
#if defined(ENABLE_OVERLOADING)
    printOperationShowProgress              ,
#endif
    setPrintOperationShowProgress           ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationStatusPropertyInfo        ,
#endif
    getPrintOperationStatus                 ,
#if defined(ENABLE_OVERLOADING)
    printOperationStatus                    ,
#endif
#if defined(ENABLE_OVERLOADING)
    PrintOperationStatusStringPropertyInfo  ,
#endif
    getPrintOperationStatusString           ,
#if defined(ENABLE_OVERLOADING)
    printOperationStatusString              ,
#endif
#if defined(ENABLE_OVERLOADING)
    PrintOperationSupportSelectionPropertyInfo,
#endif
    constructPrintOperationSupportSelection ,
    getPrintOperationSupportSelection       ,
#if defined(ENABLE_OVERLOADING)
    printOperationSupportSelection          ,
#endif
    setPrintOperationSupportSelection       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationTrackPrintStatusPropertyInfo,
#endif
    constructPrintOperationTrackPrintStatus ,
    getPrintOperationTrackPrintStatus       ,
#if defined(ENABLE_OVERLOADING)
    printOperationTrackPrintStatus          ,
#endif
    setPrintOperationTrackPrintStatus       ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationUnitPropertyInfo          ,
#endif
    constructPrintOperationUnit             ,
    getPrintOperationUnit                   ,
#if defined(ENABLE_OVERLOADING)
    printOperationUnit                      ,
#endif
    setPrintOperationUnit                   ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationUseFullPagePropertyInfo   ,
#endif
    constructPrintOperationUseFullPage      ,
    getPrintOperationUseFullPage            ,
#if defined(ENABLE_OVERLOADING)
    printOperationUseFullPage               ,
#endif
    setPrintOperationUseFullPage            ,
 
    C_PrintOperationBeginPrintCallback      ,
    PrintOperationBeginPrintCallback        ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationBeginPrintSignalInfo      ,
#endif
    afterPrintOperationBeginPrint           ,
    genClosure_PrintOperationBeginPrint     ,
    mk_PrintOperationBeginPrintCallback     ,
    noPrintOperationBeginPrintCallback      ,
    onPrintOperationBeginPrint              ,
    wrap_PrintOperationBeginPrintCallback   ,
    C_PrintOperationCreateCustomWidgetCallback,
    PrintOperationCreateCustomWidgetCallback,
#if defined(ENABLE_OVERLOADING)
    PrintOperationCreateCustomWidgetSignalInfo,
#endif
    afterPrintOperationCreateCustomWidget   ,
    genClosure_PrintOperationCreateCustomWidget,
    mk_PrintOperationCreateCustomWidgetCallback,
    noPrintOperationCreateCustomWidgetCallback,
    onPrintOperationCreateCustomWidget      ,
    wrap_PrintOperationCreateCustomWidgetCallback,
    C_PrintOperationCustomWidgetApplyCallback,
    PrintOperationCustomWidgetApplyCallback ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationCustomWidgetApplySignalInfo,
#endif
    afterPrintOperationCustomWidgetApply    ,
    genClosure_PrintOperationCustomWidgetApply,
    mk_PrintOperationCustomWidgetApplyCallback,
    noPrintOperationCustomWidgetApplyCallback,
    onPrintOperationCustomWidgetApply       ,
    wrap_PrintOperationCustomWidgetApplyCallback,
    C_PrintOperationDoneCallback            ,
    PrintOperationDoneCallback              ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationDoneSignalInfo            ,
#endif
    afterPrintOperationDone                 ,
    genClosure_PrintOperationDone           ,
    mk_PrintOperationDoneCallback           ,
    noPrintOperationDoneCallback            ,
    onPrintOperationDone                    ,
    wrap_PrintOperationDoneCallback         ,
    C_PrintOperationDrawPageCallback        ,
    PrintOperationDrawPageCallback          ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationDrawPageSignalInfo        ,
#endif
    afterPrintOperationDrawPage             ,
    genClosure_PrintOperationDrawPage       ,
    mk_PrintOperationDrawPageCallback       ,
    noPrintOperationDrawPageCallback        ,
    onPrintOperationDrawPage                ,
    wrap_PrintOperationDrawPageCallback     ,
    C_PrintOperationEndPrintCallback        ,
    PrintOperationEndPrintCallback          ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationEndPrintSignalInfo        ,
#endif
    afterPrintOperationEndPrint             ,
    genClosure_PrintOperationEndPrint       ,
    mk_PrintOperationEndPrintCallback       ,
    noPrintOperationEndPrintCallback        ,
    onPrintOperationEndPrint                ,
    wrap_PrintOperationEndPrintCallback     ,
    C_PrintOperationPaginateCallback        ,
    PrintOperationPaginateCallback          ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationPaginateSignalInfo        ,
#endif
    afterPrintOperationPaginate             ,
    genClosure_PrintOperationPaginate       ,
    mk_PrintOperationPaginateCallback       ,
    noPrintOperationPaginateCallback        ,
    onPrintOperationPaginate                ,
    wrap_PrintOperationPaginateCallback     ,
    C_PrintOperationPreviewCallback         ,
    PrintOperationPreviewCallback           ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationPreviewSignalInfo         ,
#endif
    afterPrintOperationPreview              ,
    genClosure_PrintOperationPreview        ,
    mk_PrintOperationPreviewCallback        ,
    noPrintOperationPreviewCallback         ,
    onPrintOperationPreview                 ,
    wrap_PrintOperationPreviewCallback      ,
    C_PrintOperationRequestPageSetupCallback,
    PrintOperationRequestPageSetupCallback  ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationRequestPageSetupSignalInfo,
#endif
    afterPrintOperationRequestPageSetup     ,
    genClosure_PrintOperationRequestPageSetup,
    mk_PrintOperationRequestPageSetupCallback,
    noPrintOperationRequestPageSetupCallback,
    onPrintOperationRequestPageSetup        ,
    wrap_PrintOperationRequestPageSetupCallback,
    C_PrintOperationStatusChangedCallback   ,
    PrintOperationStatusChangedCallback     ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationStatusChangedSignalInfo   ,
#endif
    afterPrintOperationStatusChanged        ,
    genClosure_PrintOperationStatusChanged  ,
    mk_PrintOperationStatusChangedCallback  ,
    noPrintOperationStatusChangedCallback   ,
    onPrintOperationStatusChanged           ,
    wrap_PrintOperationStatusChangedCallback,
    C_PrintOperationUpdateCustomWidgetCallback,
    PrintOperationUpdateCustomWidgetCallback,
#if defined(ENABLE_OVERLOADING)
    PrintOperationUpdateCustomWidgetSignalInfo,
#endif
    afterPrintOperationUpdateCustomWidget   ,
    genClosure_PrintOperationUpdateCustomWidget,
    mk_PrintOperationUpdateCustomWidgetCallback,
    noPrintOperationUpdateCustomWidgetCallback,
    onPrintOperationUpdateCustomWidget      ,
    wrap_PrintOperationUpdateCustomWidgetCallback,
    ) 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.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.PrintOperationPreview as Gtk.PrintOperationPreview
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Objects.PrintContext as Gtk.PrintContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window
newtype PrintOperation = PrintOperation (SP.ManagedPtr PrintOperation)
    deriving (PrintOperation -> PrintOperation -> Bool
(PrintOperation -> PrintOperation -> Bool)
-> (PrintOperation -> PrintOperation -> Bool) -> Eq PrintOperation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrintOperation -> PrintOperation -> Bool
$c/= :: PrintOperation -> PrintOperation -> Bool
== :: PrintOperation -> PrintOperation -> Bool
$c== :: PrintOperation -> PrintOperation -> Bool
Eq)
instance SP.ManagedPtrNewtype PrintOperation where
    toManagedPtr :: PrintOperation -> ManagedPtr PrintOperation
toManagedPtr (PrintOperation ManagedPtr PrintOperation
p) = ManagedPtr PrintOperation
p
foreign import ccall "gtk_print_operation_get_type"
    c_gtk_print_operation_get_type :: IO B.Types.GType
instance B.Types.TypedObject PrintOperation where
    glibType :: IO GType
glibType = IO GType
c_gtk_print_operation_get_type
instance B.Types.GObject PrintOperation
class (SP.GObject o, O.IsDescendantOf PrintOperation o) => IsPrintOperation o
instance (SP.GObject o, O.IsDescendantOf PrintOperation o) => IsPrintOperation o
instance O.HasParentTypes PrintOperation
type instance O.ParentTypes PrintOperation = '[GObject.Object.Object, Gtk.PrintOperationPreview.PrintOperationPreview]
toPrintOperation :: (MIO.MonadIO m, IsPrintOperation o) => o -> m PrintOperation
toPrintOperation :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m PrintOperation
toPrintOperation = IO PrintOperation -> m PrintOperation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PrintOperation -> m PrintOperation)
-> (o -> IO PrintOperation) -> o -> m PrintOperation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr PrintOperation -> PrintOperation)
-> o -> IO PrintOperation
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr PrintOperation -> PrintOperation
PrintOperation
instance B.GValue.IsGValue (Maybe PrintOperation) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_print_operation_get_type
    gvalueSet_ :: Ptr GValue -> Maybe PrintOperation -> IO ()
gvalueSet_ Ptr GValue
gv Maybe PrintOperation
P.Nothing = Ptr GValue -> Ptr PrintOperation -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr PrintOperation
forall a. Ptr a
FP.nullPtr :: FP.Ptr PrintOperation)
    gvalueSet_ Ptr GValue
gv (P.Just PrintOperation
obj) = PrintOperation -> (Ptr PrintOperation -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PrintOperation
obj (Ptr GValue -> Ptr PrintOperation -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe PrintOperation)
gvalueGet_ Ptr GValue
gv = do
        Ptr PrintOperation
ptr <- Ptr GValue -> IO (Ptr PrintOperation)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr PrintOperation)
        if Ptr PrintOperation
ptr Ptr PrintOperation -> Ptr PrintOperation -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr PrintOperation
forall a. Ptr a
FP.nullPtr
        then PrintOperation -> Maybe PrintOperation
forall a. a -> Maybe a
P.Just (PrintOperation -> Maybe PrintOperation)
-> IO PrintOperation -> IO (Maybe PrintOperation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr PrintOperation -> PrintOperation)
-> Ptr PrintOperation -> IO PrintOperation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr PrintOperation -> PrintOperation
PrintOperation Ptr PrintOperation
ptr
        else Maybe PrintOperation -> IO (Maybe PrintOperation)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PrintOperation
forall a. Maybe a
P.Nothing
        
    
#if defined(ENABLE_OVERLOADING)
type family ResolvePrintOperationMethod (t :: Symbol) (o :: *) :: * where
    ResolvePrintOperationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePrintOperationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePrintOperationMethod "cancel" o = PrintOperationCancelMethodInfo
    ResolvePrintOperationMethod "drawPageFinish" o = PrintOperationDrawPageFinishMethodInfo
    ResolvePrintOperationMethod "endPreview" o = Gtk.PrintOperationPreview.PrintOperationPreviewEndPreviewMethodInfo
    ResolvePrintOperationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePrintOperationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePrintOperationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePrintOperationMethod "isFinished" o = PrintOperationIsFinishedMethodInfo
    ResolvePrintOperationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePrintOperationMethod "isSelected" o = Gtk.PrintOperationPreview.PrintOperationPreviewIsSelectedMethodInfo
    ResolvePrintOperationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePrintOperationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePrintOperationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePrintOperationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePrintOperationMethod "renderPage" o = Gtk.PrintOperationPreview.PrintOperationPreviewRenderPageMethodInfo
    ResolvePrintOperationMethod "run" o = PrintOperationRunMethodInfo
    ResolvePrintOperationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePrintOperationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePrintOperationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePrintOperationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePrintOperationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePrintOperationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePrintOperationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePrintOperationMethod "getDefaultPageSetup" o = PrintOperationGetDefaultPageSetupMethodInfo
    ResolvePrintOperationMethod "getEmbedPageSetup" o = PrintOperationGetEmbedPageSetupMethodInfo
    ResolvePrintOperationMethod "getError" o = PrintOperationGetErrorMethodInfo
    ResolvePrintOperationMethod "getHasSelection" o = PrintOperationGetHasSelectionMethodInfo
    ResolvePrintOperationMethod "getNPagesToPrint" o = PrintOperationGetNPagesToPrintMethodInfo
    ResolvePrintOperationMethod "getPrintSettings" o = PrintOperationGetPrintSettingsMethodInfo
    ResolvePrintOperationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePrintOperationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePrintOperationMethod "getStatus" o = PrintOperationGetStatusMethodInfo
    ResolvePrintOperationMethod "getStatusString" o = PrintOperationGetStatusStringMethodInfo
    ResolvePrintOperationMethod "getSupportSelection" o = PrintOperationGetSupportSelectionMethodInfo
    ResolvePrintOperationMethod "setAllowAsync" o = PrintOperationSetAllowAsyncMethodInfo
    ResolvePrintOperationMethod "setCurrentPage" o = PrintOperationSetCurrentPageMethodInfo
    ResolvePrintOperationMethod "setCustomTabLabel" o = PrintOperationSetCustomTabLabelMethodInfo
    ResolvePrintOperationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePrintOperationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePrintOperationMethod "setDefaultPageSetup" o = PrintOperationSetDefaultPageSetupMethodInfo
    ResolvePrintOperationMethod "setDeferDrawing" o = PrintOperationSetDeferDrawingMethodInfo
    ResolvePrintOperationMethod "setEmbedPageSetup" o = PrintOperationSetEmbedPageSetupMethodInfo
    ResolvePrintOperationMethod "setExportFilename" o = PrintOperationSetExportFilenameMethodInfo
    ResolvePrintOperationMethod "setHasSelection" o = PrintOperationSetHasSelectionMethodInfo
    ResolvePrintOperationMethod "setJobName" o = PrintOperationSetJobNameMethodInfo
    ResolvePrintOperationMethod "setNPages" o = PrintOperationSetNPagesMethodInfo
    ResolvePrintOperationMethod "setPrintSettings" o = PrintOperationSetPrintSettingsMethodInfo
    ResolvePrintOperationMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePrintOperationMethod "setShowProgress" o = PrintOperationSetShowProgressMethodInfo
    ResolvePrintOperationMethod "setSupportSelection" o = PrintOperationSetSupportSelectionMethodInfo
    ResolvePrintOperationMethod "setTrackPrintStatus" o = PrintOperationSetTrackPrintStatusMethodInfo
    ResolvePrintOperationMethod "setUnit" o = PrintOperationSetUnitMethodInfo
    ResolvePrintOperationMethod "setUseFullPage" o = PrintOperationSetUseFullPageMethodInfo
    ResolvePrintOperationMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePrintOperationMethod t PrintOperation, O.OverloadedMethod info PrintOperation p) => OL.IsLabel t (PrintOperation -> 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 ~ ResolvePrintOperationMethod t PrintOperation, O.OverloadedMethod info PrintOperation p, R.HasField t PrintOperation p) => R.HasField t PrintOperation p where
    getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePrintOperationMethod t PrintOperation, O.OverloadedMethodInfo info PrintOperation) => OL.IsLabel t (O.MethodProxy info PrintOperation) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif
#endif
type PrintOperationBeginPrintCallback =
    Gtk.PrintContext.PrintContext
    
    -> IO ()
noPrintOperationBeginPrintCallback :: Maybe PrintOperationBeginPrintCallback
noPrintOperationBeginPrintCallback :: Maybe PrintOperationBeginPrintCallback
noPrintOperationBeginPrintCallback = Maybe PrintOperationBeginPrintCallback
forall a. Maybe a
Nothing
type C_PrintOperationBeginPrintCallback =
    Ptr () ->                               
    Ptr Gtk.PrintContext.PrintContext ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_PrintOperationBeginPrintCallback :: C_PrintOperationBeginPrintCallback -> IO (FunPtr C_PrintOperationBeginPrintCallback)
genClosure_PrintOperationBeginPrint :: MonadIO m => PrintOperationBeginPrintCallback -> m (GClosure C_PrintOperationBeginPrintCallback)
genClosure_PrintOperationBeginPrint :: forall (m :: * -> *).
MonadIO m =>
PrintOperationBeginPrintCallback
-> m (GClosure C_PrintOperationBeginPrintCallback)
genClosure_PrintOperationBeginPrint PrintOperationBeginPrintCallback
cb = IO (GClosure C_PrintOperationBeginPrintCallback)
-> m (GClosure C_PrintOperationBeginPrintCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationBeginPrintCallback)
 -> m (GClosure C_PrintOperationBeginPrintCallback))
-> IO (GClosure C_PrintOperationBeginPrintCallback)
-> m (GClosure C_PrintOperationBeginPrintCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationBeginPrintCallback
cb' = PrintOperationBeginPrintCallback
-> C_PrintOperationBeginPrintCallback
wrap_PrintOperationBeginPrintCallback PrintOperationBeginPrintCallback
cb
    C_PrintOperationBeginPrintCallback
-> IO (FunPtr C_PrintOperationBeginPrintCallback)
mk_PrintOperationBeginPrintCallback C_PrintOperationBeginPrintCallback
cb' IO (FunPtr C_PrintOperationBeginPrintCallback)
-> (FunPtr C_PrintOperationBeginPrintCallback
    -> IO (GClosure C_PrintOperationBeginPrintCallback))
-> IO (GClosure C_PrintOperationBeginPrintCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationBeginPrintCallback
-> IO (GClosure C_PrintOperationBeginPrintCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationBeginPrintCallback ::
    PrintOperationBeginPrintCallback ->
    C_PrintOperationBeginPrintCallback
wrap_PrintOperationBeginPrintCallback :: PrintOperationBeginPrintCallback
-> C_PrintOperationBeginPrintCallback
wrap_PrintOperationBeginPrintCallback PrintOperationBeginPrintCallback
_cb Ptr ()
_ Ptr PrintContext
context Ptr ()
_ = do
    PrintContext
context' <- ((ManagedPtr PrintContext -> PrintContext)
-> Ptr PrintContext -> IO PrintContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintContext -> PrintContext
Gtk.PrintContext.PrintContext) Ptr PrintContext
context
    PrintOperationBeginPrintCallback
_cb  PrintContext
context'
onPrintOperationBeginPrint :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationBeginPrintCallback -> m SignalHandlerId
onPrintOperationBeginPrint :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationBeginPrintCallback -> m SignalHandlerId
onPrintOperationBeginPrint a
obj PrintOperationBeginPrintCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationBeginPrintCallback
cb' = PrintOperationBeginPrintCallback
-> C_PrintOperationBeginPrintCallback
wrap_PrintOperationBeginPrintCallback PrintOperationBeginPrintCallback
cb
    FunPtr C_PrintOperationBeginPrintCallback
cb'' <- C_PrintOperationBeginPrintCallback
-> IO (FunPtr C_PrintOperationBeginPrintCallback)
mk_PrintOperationBeginPrintCallback C_PrintOperationBeginPrintCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationBeginPrintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"begin-print" FunPtr C_PrintOperationBeginPrintCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationBeginPrint :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationBeginPrintCallback -> m SignalHandlerId
afterPrintOperationBeginPrint :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationBeginPrintCallback -> m SignalHandlerId
afterPrintOperationBeginPrint a
obj PrintOperationBeginPrintCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationBeginPrintCallback
cb' = PrintOperationBeginPrintCallback
-> C_PrintOperationBeginPrintCallback
wrap_PrintOperationBeginPrintCallback PrintOperationBeginPrintCallback
cb
    FunPtr C_PrintOperationBeginPrintCallback
cb'' <- C_PrintOperationBeginPrintCallback
-> IO (FunPtr C_PrintOperationBeginPrintCallback)
mk_PrintOperationBeginPrintCallback C_PrintOperationBeginPrintCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationBeginPrintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"begin-print" FunPtr C_PrintOperationBeginPrintCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationBeginPrintSignalInfo
instance SignalInfo PrintOperationBeginPrintSignalInfo where
    type HaskellCallbackType PrintOperationBeginPrintSignalInfo = PrintOperationBeginPrintCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationBeginPrintCallback cb
        cb'' <- mk_PrintOperationBeginPrintCallback cb'
        connectSignalFunPtr obj "begin-print" cb'' connectMode detail
#endif
type PrintOperationCreateCustomWidgetCallback =
    IO GObject.Object.Object
    
    
noPrintOperationCreateCustomWidgetCallback :: Maybe PrintOperationCreateCustomWidgetCallback
noPrintOperationCreateCustomWidgetCallback :: Maybe PrintOperationCreateCustomWidgetCallback
noPrintOperationCreateCustomWidgetCallback = Maybe PrintOperationCreateCustomWidgetCallback
forall a. Maybe a
Nothing
type C_PrintOperationCreateCustomWidgetCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO (Ptr GObject.Object.Object)
foreign import ccall "wrapper"
    mk_PrintOperationCreateCustomWidgetCallback :: C_PrintOperationCreateCustomWidgetCallback -> IO (FunPtr C_PrintOperationCreateCustomWidgetCallback)
genClosure_PrintOperationCreateCustomWidget :: MonadIO m => PrintOperationCreateCustomWidgetCallback -> m (GClosure C_PrintOperationCreateCustomWidgetCallback)
genClosure_PrintOperationCreateCustomWidget :: forall (m :: * -> *).
MonadIO m =>
PrintOperationCreateCustomWidgetCallback
-> m (GClosure C_PrintOperationCreateCustomWidgetCallback)
genClosure_PrintOperationCreateCustomWidget PrintOperationCreateCustomWidgetCallback
cb = IO (GClosure C_PrintOperationCreateCustomWidgetCallback)
-> m (GClosure C_PrintOperationCreateCustomWidgetCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationCreateCustomWidgetCallback)
 -> m (GClosure C_PrintOperationCreateCustomWidgetCallback))
-> IO (GClosure C_PrintOperationCreateCustomWidgetCallback)
-> m (GClosure C_PrintOperationCreateCustomWidgetCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationCreateCustomWidgetCallback
cb' = PrintOperationCreateCustomWidgetCallback
-> C_PrintOperationCreateCustomWidgetCallback
wrap_PrintOperationCreateCustomWidgetCallback PrintOperationCreateCustomWidgetCallback
cb
    C_PrintOperationCreateCustomWidgetCallback
-> IO (FunPtr C_PrintOperationCreateCustomWidgetCallback)
mk_PrintOperationCreateCustomWidgetCallback C_PrintOperationCreateCustomWidgetCallback
cb' IO (FunPtr C_PrintOperationCreateCustomWidgetCallback)
-> (FunPtr C_PrintOperationCreateCustomWidgetCallback
    -> IO (GClosure C_PrintOperationCreateCustomWidgetCallback))
-> IO (GClosure C_PrintOperationCreateCustomWidgetCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationCreateCustomWidgetCallback
-> IO (GClosure C_PrintOperationCreateCustomWidgetCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationCreateCustomWidgetCallback ::
    PrintOperationCreateCustomWidgetCallback ->
    C_PrintOperationCreateCustomWidgetCallback
wrap_PrintOperationCreateCustomWidgetCallback :: PrintOperationCreateCustomWidgetCallback
-> C_PrintOperationCreateCustomWidgetCallback
wrap_PrintOperationCreateCustomWidgetCallback PrintOperationCreateCustomWidgetCallback
_cb Ptr ()
_ Ptr ()
_ = do
    Object
result <- PrintOperationCreateCustomWidgetCallback
_cb 
    Ptr Object
result' <- Object -> IO (Ptr Object)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr Object
result
    Ptr Object -> IO (Ptr Object)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Object
result'
onPrintOperationCreateCustomWidget :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationCreateCustomWidgetCallback -> m SignalHandlerId
onPrintOperationCreateCustomWidget :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationCreateCustomWidgetCallback -> m SignalHandlerId
onPrintOperationCreateCustomWidget a
obj PrintOperationCreateCustomWidgetCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationCreateCustomWidgetCallback
cb' = PrintOperationCreateCustomWidgetCallback
-> C_PrintOperationCreateCustomWidgetCallback
wrap_PrintOperationCreateCustomWidgetCallback PrintOperationCreateCustomWidgetCallback
cb
    FunPtr C_PrintOperationCreateCustomWidgetCallback
cb'' <- C_PrintOperationCreateCustomWidgetCallback
-> IO (FunPtr C_PrintOperationCreateCustomWidgetCallback)
mk_PrintOperationCreateCustomWidgetCallback C_PrintOperationCreateCustomWidgetCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationCreateCustomWidgetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"create-custom-widget" FunPtr C_PrintOperationCreateCustomWidgetCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationCreateCustomWidget :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationCreateCustomWidgetCallback -> m SignalHandlerId
afterPrintOperationCreateCustomWidget :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationCreateCustomWidgetCallback -> m SignalHandlerId
afterPrintOperationCreateCustomWidget a
obj PrintOperationCreateCustomWidgetCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationCreateCustomWidgetCallback
cb' = PrintOperationCreateCustomWidgetCallback
-> C_PrintOperationCreateCustomWidgetCallback
wrap_PrintOperationCreateCustomWidgetCallback PrintOperationCreateCustomWidgetCallback
cb
    FunPtr C_PrintOperationCreateCustomWidgetCallback
cb'' <- C_PrintOperationCreateCustomWidgetCallback
-> IO (FunPtr C_PrintOperationCreateCustomWidgetCallback)
mk_PrintOperationCreateCustomWidgetCallback C_PrintOperationCreateCustomWidgetCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationCreateCustomWidgetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"create-custom-widget" FunPtr C_PrintOperationCreateCustomWidgetCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationCreateCustomWidgetSignalInfo
instance SignalInfo PrintOperationCreateCustomWidgetSignalInfo where
    type HaskellCallbackType PrintOperationCreateCustomWidgetSignalInfo = PrintOperationCreateCustomWidgetCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationCreateCustomWidgetCallback cb
        cb'' <- mk_PrintOperationCreateCustomWidgetCallback cb'
        connectSignalFunPtr obj "create-custom-widget" cb'' connectMode detail
#endif
type PrintOperationCustomWidgetApplyCallback =
    Gtk.Widget.Widget
    
    -> IO ()
noPrintOperationCustomWidgetApplyCallback :: Maybe PrintOperationCustomWidgetApplyCallback
noPrintOperationCustomWidgetApplyCallback :: Maybe PrintOperationCustomWidgetApplyCallback
noPrintOperationCustomWidgetApplyCallback = Maybe PrintOperationCustomWidgetApplyCallback
forall a. Maybe a
Nothing
type C_PrintOperationCustomWidgetApplyCallback =
    Ptr () ->                               
    Ptr Gtk.Widget.Widget ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_PrintOperationCustomWidgetApplyCallback :: C_PrintOperationCustomWidgetApplyCallback -> IO (FunPtr C_PrintOperationCustomWidgetApplyCallback)
genClosure_PrintOperationCustomWidgetApply :: MonadIO m => PrintOperationCustomWidgetApplyCallback -> m (GClosure C_PrintOperationCustomWidgetApplyCallback)
genClosure_PrintOperationCustomWidgetApply :: forall (m :: * -> *).
MonadIO m =>
PrintOperationCustomWidgetApplyCallback
-> m (GClosure C_PrintOperationCustomWidgetApplyCallback)
genClosure_PrintOperationCustomWidgetApply PrintOperationCustomWidgetApplyCallback
cb = IO (GClosure C_PrintOperationCustomWidgetApplyCallback)
-> m (GClosure C_PrintOperationCustomWidgetApplyCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationCustomWidgetApplyCallback)
 -> m (GClosure C_PrintOperationCustomWidgetApplyCallback))
-> IO (GClosure C_PrintOperationCustomWidgetApplyCallback)
-> m (GClosure C_PrintOperationCustomWidgetApplyCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationCustomWidgetApplyCallback
cb' = PrintOperationCustomWidgetApplyCallback
-> C_PrintOperationCustomWidgetApplyCallback
wrap_PrintOperationCustomWidgetApplyCallback PrintOperationCustomWidgetApplyCallback
cb
    C_PrintOperationCustomWidgetApplyCallback
-> IO (FunPtr C_PrintOperationCustomWidgetApplyCallback)
mk_PrintOperationCustomWidgetApplyCallback C_PrintOperationCustomWidgetApplyCallback
cb' IO (FunPtr C_PrintOperationCustomWidgetApplyCallback)
-> (FunPtr C_PrintOperationCustomWidgetApplyCallback
    -> IO (GClosure C_PrintOperationCustomWidgetApplyCallback))
-> IO (GClosure C_PrintOperationCustomWidgetApplyCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationCustomWidgetApplyCallback
-> IO (GClosure C_PrintOperationCustomWidgetApplyCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationCustomWidgetApplyCallback ::
    PrintOperationCustomWidgetApplyCallback ->
    C_PrintOperationCustomWidgetApplyCallback
wrap_PrintOperationCustomWidgetApplyCallback :: PrintOperationCustomWidgetApplyCallback
-> C_PrintOperationCustomWidgetApplyCallback
wrap_PrintOperationCustomWidgetApplyCallback PrintOperationCustomWidgetApplyCallback
_cb Ptr ()
_ Ptr Widget
widget Ptr ()
_ = do
    Widget
widget' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
widget
    PrintOperationCustomWidgetApplyCallback
_cb  Widget
widget'
onPrintOperationCustomWidgetApply :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationCustomWidgetApplyCallback -> m SignalHandlerId
onPrintOperationCustomWidgetApply :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationCustomWidgetApplyCallback -> m SignalHandlerId
onPrintOperationCustomWidgetApply a
obj PrintOperationCustomWidgetApplyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationCustomWidgetApplyCallback
cb' = PrintOperationCustomWidgetApplyCallback
-> C_PrintOperationCustomWidgetApplyCallback
wrap_PrintOperationCustomWidgetApplyCallback PrintOperationCustomWidgetApplyCallback
cb
    FunPtr C_PrintOperationCustomWidgetApplyCallback
cb'' <- C_PrintOperationCustomWidgetApplyCallback
-> IO (FunPtr C_PrintOperationCustomWidgetApplyCallback)
mk_PrintOperationCustomWidgetApplyCallback C_PrintOperationCustomWidgetApplyCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationCustomWidgetApplyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"custom-widget-apply" FunPtr C_PrintOperationCustomWidgetApplyCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationCustomWidgetApply :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationCustomWidgetApplyCallback -> m SignalHandlerId
afterPrintOperationCustomWidgetApply :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationCustomWidgetApplyCallback -> m SignalHandlerId
afterPrintOperationCustomWidgetApply a
obj PrintOperationCustomWidgetApplyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationCustomWidgetApplyCallback
cb' = PrintOperationCustomWidgetApplyCallback
-> C_PrintOperationCustomWidgetApplyCallback
wrap_PrintOperationCustomWidgetApplyCallback PrintOperationCustomWidgetApplyCallback
cb
    FunPtr C_PrintOperationCustomWidgetApplyCallback
cb'' <- C_PrintOperationCustomWidgetApplyCallback
-> IO (FunPtr C_PrintOperationCustomWidgetApplyCallback)
mk_PrintOperationCustomWidgetApplyCallback C_PrintOperationCustomWidgetApplyCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationCustomWidgetApplyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"custom-widget-apply" FunPtr C_PrintOperationCustomWidgetApplyCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationCustomWidgetApplySignalInfo
instance SignalInfo PrintOperationCustomWidgetApplySignalInfo where
    type HaskellCallbackType PrintOperationCustomWidgetApplySignalInfo = PrintOperationCustomWidgetApplyCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationCustomWidgetApplyCallback cb
        cb'' <- mk_PrintOperationCustomWidgetApplyCallback cb'
        connectSignalFunPtr obj "custom-widget-apply" cb'' connectMode detail
#endif
type PrintOperationDoneCallback =
    Gtk.Enums.PrintOperationResult
    
    -> IO ()
noPrintOperationDoneCallback :: Maybe PrintOperationDoneCallback
noPrintOperationDoneCallback :: Maybe PrintOperationDoneCallback
noPrintOperationDoneCallback = Maybe PrintOperationDoneCallback
forall a. Maybe a
Nothing
type C_PrintOperationDoneCallback =
    Ptr () ->                               
    CUInt ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_PrintOperationDoneCallback :: C_PrintOperationDoneCallback -> IO (FunPtr C_PrintOperationDoneCallback)
genClosure_PrintOperationDone :: MonadIO m => PrintOperationDoneCallback -> m (GClosure C_PrintOperationDoneCallback)
genClosure_PrintOperationDone :: forall (m :: * -> *).
MonadIO m =>
PrintOperationDoneCallback
-> m (GClosure C_PrintOperationDoneCallback)
genClosure_PrintOperationDone PrintOperationDoneCallback
cb = IO (GClosure C_PrintOperationDoneCallback)
-> m (GClosure C_PrintOperationDoneCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationDoneCallback)
 -> m (GClosure C_PrintOperationDoneCallback))
-> IO (GClosure C_PrintOperationDoneCallback)
-> m (GClosure C_PrintOperationDoneCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationDoneCallback
cb' = PrintOperationDoneCallback -> C_PrintOperationDoneCallback
wrap_PrintOperationDoneCallback PrintOperationDoneCallback
cb
    C_PrintOperationDoneCallback
-> IO (FunPtr C_PrintOperationDoneCallback)
mk_PrintOperationDoneCallback C_PrintOperationDoneCallback
cb' IO (FunPtr C_PrintOperationDoneCallback)
-> (FunPtr C_PrintOperationDoneCallback
    -> IO (GClosure C_PrintOperationDoneCallback))
-> IO (GClosure C_PrintOperationDoneCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationDoneCallback
-> IO (GClosure C_PrintOperationDoneCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationDoneCallback ::
    PrintOperationDoneCallback ->
    C_PrintOperationDoneCallback
wrap_PrintOperationDoneCallback :: PrintOperationDoneCallback -> C_PrintOperationDoneCallback
wrap_PrintOperationDoneCallback PrintOperationDoneCallback
_cb Ptr ()
_ CUInt
result_ Ptr ()
_ = do
    let result_' :: PrintOperationResult
result_' = (Int -> PrintOperationResult
forall a. Enum a => Int -> a
toEnum (Int -> PrintOperationResult)
-> (CUInt -> Int) -> CUInt -> PrintOperationResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result_
    PrintOperationDoneCallback
_cb  PrintOperationResult
result_'
onPrintOperationDone :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationDoneCallback -> m SignalHandlerId
onPrintOperationDone :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationDoneCallback -> m SignalHandlerId
onPrintOperationDone a
obj PrintOperationDoneCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationDoneCallback
cb' = PrintOperationDoneCallback -> C_PrintOperationDoneCallback
wrap_PrintOperationDoneCallback PrintOperationDoneCallback
cb
    FunPtr C_PrintOperationDoneCallback
cb'' <- C_PrintOperationDoneCallback
-> IO (FunPtr C_PrintOperationDoneCallback)
mk_PrintOperationDoneCallback C_PrintOperationDoneCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationDoneCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"done" FunPtr C_PrintOperationDoneCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationDone :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationDoneCallback -> m SignalHandlerId
afterPrintOperationDone :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationDoneCallback -> m SignalHandlerId
afterPrintOperationDone a
obj PrintOperationDoneCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationDoneCallback
cb' = PrintOperationDoneCallback -> C_PrintOperationDoneCallback
wrap_PrintOperationDoneCallback PrintOperationDoneCallback
cb
    FunPtr C_PrintOperationDoneCallback
cb'' <- C_PrintOperationDoneCallback
-> IO (FunPtr C_PrintOperationDoneCallback)
mk_PrintOperationDoneCallback C_PrintOperationDoneCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationDoneCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"done" FunPtr C_PrintOperationDoneCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationDoneSignalInfo
instance SignalInfo PrintOperationDoneSignalInfo where
    type HaskellCallbackType PrintOperationDoneSignalInfo = PrintOperationDoneCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationDoneCallback cb
        cb'' <- mk_PrintOperationDoneCallback cb'
        connectSignalFunPtr obj "done" cb'' connectMode detail
#endif
type PrintOperationDrawPageCallback =
    Gtk.PrintContext.PrintContext
    
    -> Int32
    
    -> IO ()
noPrintOperationDrawPageCallback :: Maybe PrintOperationDrawPageCallback
noPrintOperationDrawPageCallback :: Maybe PrintOperationDrawPageCallback
noPrintOperationDrawPageCallback = Maybe PrintOperationDrawPageCallback
forall a. Maybe a
Nothing
type C_PrintOperationDrawPageCallback =
    Ptr () ->                               
    Ptr Gtk.PrintContext.PrintContext ->
    Int32 ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_PrintOperationDrawPageCallback :: C_PrintOperationDrawPageCallback -> IO (FunPtr C_PrintOperationDrawPageCallback)
genClosure_PrintOperationDrawPage :: MonadIO m => PrintOperationDrawPageCallback -> m (GClosure C_PrintOperationDrawPageCallback)
genClosure_PrintOperationDrawPage :: forall (m :: * -> *).
MonadIO m =>
PrintOperationDrawPageCallback
-> m (GClosure C_PrintOperationDrawPageCallback)
genClosure_PrintOperationDrawPage PrintOperationDrawPageCallback
cb = IO (GClosure C_PrintOperationDrawPageCallback)
-> m (GClosure C_PrintOperationDrawPageCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationDrawPageCallback)
 -> m (GClosure C_PrintOperationDrawPageCallback))
-> IO (GClosure C_PrintOperationDrawPageCallback)
-> m (GClosure C_PrintOperationDrawPageCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationDrawPageCallback
cb' = PrintOperationDrawPageCallback -> C_PrintOperationDrawPageCallback
wrap_PrintOperationDrawPageCallback PrintOperationDrawPageCallback
cb
    C_PrintOperationDrawPageCallback
-> IO (FunPtr C_PrintOperationDrawPageCallback)
mk_PrintOperationDrawPageCallback C_PrintOperationDrawPageCallback
cb' IO (FunPtr C_PrintOperationDrawPageCallback)
-> (FunPtr C_PrintOperationDrawPageCallback
    -> IO (GClosure C_PrintOperationDrawPageCallback))
-> IO (GClosure C_PrintOperationDrawPageCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationDrawPageCallback
-> IO (GClosure C_PrintOperationDrawPageCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationDrawPageCallback ::
    PrintOperationDrawPageCallback ->
    C_PrintOperationDrawPageCallback
wrap_PrintOperationDrawPageCallback :: PrintOperationDrawPageCallback -> C_PrintOperationDrawPageCallback
wrap_PrintOperationDrawPageCallback PrintOperationDrawPageCallback
_cb Ptr ()
_ Ptr PrintContext
context Int32
pageNr Ptr ()
_ = do
    PrintContext
context' <- ((ManagedPtr PrintContext -> PrintContext)
-> Ptr PrintContext -> IO PrintContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintContext -> PrintContext
Gtk.PrintContext.PrintContext) Ptr PrintContext
context
    PrintOperationDrawPageCallback
_cb  PrintContext
context' Int32
pageNr
onPrintOperationDrawPage :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationDrawPageCallback -> m SignalHandlerId
onPrintOperationDrawPage :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationDrawPageCallback -> m SignalHandlerId
onPrintOperationDrawPage a
obj PrintOperationDrawPageCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationDrawPageCallback
cb' = PrintOperationDrawPageCallback -> C_PrintOperationDrawPageCallback
wrap_PrintOperationDrawPageCallback PrintOperationDrawPageCallback
cb
    FunPtr C_PrintOperationDrawPageCallback
cb'' <- C_PrintOperationDrawPageCallback
-> IO (FunPtr C_PrintOperationDrawPageCallback)
mk_PrintOperationDrawPageCallback C_PrintOperationDrawPageCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationDrawPageCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"draw-page" FunPtr C_PrintOperationDrawPageCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationDrawPage :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationDrawPageCallback -> m SignalHandlerId
afterPrintOperationDrawPage :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationDrawPageCallback -> m SignalHandlerId
afterPrintOperationDrawPage a
obj PrintOperationDrawPageCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationDrawPageCallback
cb' = PrintOperationDrawPageCallback -> C_PrintOperationDrawPageCallback
wrap_PrintOperationDrawPageCallback PrintOperationDrawPageCallback
cb
    FunPtr C_PrintOperationDrawPageCallback
cb'' <- C_PrintOperationDrawPageCallback
-> IO (FunPtr C_PrintOperationDrawPageCallback)
mk_PrintOperationDrawPageCallback C_PrintOperationDrawPageCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationDrawPageCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"draw-page" FunPtr C_PrintOperationDrawPageCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationDrawPageSignalInfo
instance SignalInfo PrintOperationDrawPageSignalInfo where
    type HaskellCallbackType PrintOperationDrawPageSignalInfo = PrintOperationDrawPageCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationDrawPageCallback cb
        cb'' <- mk_PrintOperationDrawPageCallback cb'
        connectSignalFunPtr obj "draw-page" cb'' connectMode detail
#endif
type PrintOperationEndPrintCallback =
    Gtk.PrintContext.PrintContext
    
    -> IO ()
noPrintOperationEndPrintCallback :: Maybe PrintOperationEndPrintCallback
noPrintOperationEndPrintCallback :: Maybe PrintOperationBeginPrintCallback
noPrintOperationEndPrintCallback = Maybe PrintOperationBeginPrintCallback
forall a. Maybe a
Nothing
type C_PrintOperationEndPrintCallback =
    Ptr () ->                               
    Ptr Gtk.PrintContext.PrintContext ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_PrintOperationEndPrintCallback :: C_PrintOperationEndPrintCallback -> IO (FunPtr C_PrintOperationEndPrintCallback)
genClosure_PrintOperationEndPrint :: MonadIO m => PrintOperationEndPrintCallback -> m (GClosure C_PrintOperationEndPrintCallback)
genClosure_PrintOperationEndPrint :: forall (m :: * -> *).
MonadIO m =>
PrintOperationBeginPrintCallback
-> m (GClosure C_PrintOperationBeginPrintCallback)
genClosure_PrintOperationEndPrint PrintOperationBeginPrintCallback
cb = IO (GClosure C_PrintOperationBeginPrintCallback)
-> m (GClosure C_PrintOperationBeginPrintCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationBeginPrintCallback)
 -> m (GClosure C_PrintOperationBeginPrintCallback))
-> IO (GClosure C_PrintOperationBeginPrintCallback)
-> m (GClosure C_PrintOperationBeginPrintCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationBeginPrintCallback
cb' = PrintOperationBeginPrintCallback
-> C_PrintOperationBeginPrintCallback
wrap_PrintOperationEndPrintCallback PrintOperationBeginPrintCallback
cb
    C_PrintOperationBeginPrintCallback
-> IO (FunPtr C_PrintOperationBeginPrintCallback)
mk_PrintOperationEndPrintCallback C_PrintOperationBeginPrintCallback
cb' IO (FunPtr C_PrintOperationBeginPrintCallback)
-> (FunPtr C_PrintOperationBeginPrintCallback
    -> IO (GClosure C_PrintOperationBeginPrintCallback))
-> IO (GClosure C_PrintOperationBeginPrintCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationBeginPrintCallback
-> IO (GClosure C_PrintOperationBeginPrintCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationEndPrintCallback ::
    PrintOperationEndPrintCallback ->
    C_PrintOperationEndPrintCallback
wrap_PrintOperationEndPrintCallback :: PrintOperationBeginPrintCallback
-> C_PrintOperationBeginPrintCallback
wrap_PrintOperationEndPrintCallback PrintOperationBeginPrintCallback
_cb Ptr ()
_ Ptr PrintContext
context Ptr ()
_ = do
    PrintContext
context' <- ((ManagedPtr PrintContext -> PrintContext)
-> Ptr PrintContext -> IO PrintContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintContext -> PrintContext
Gtk.PrintContext.PrintContext) Ptr PrintContext
context
    PrintOperationBeginPrintCallback
_cb  PrintContext
context'
onPrintOperationEndPrint :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationEndPrintCallback -> m SignalHandlerId
onPrintOperationEndPrint :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationBeginPrintCallback -> m SignalHandlerId
onPrintOperationEndPrint a
obj PrintOperationBeginPrintCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationBeginPrintCallback
cb' = PrintOperationBeginPrintCallback
-> C_PrintOperationBeginPrintCallback
wrap_PrintOperationEndPrintCallback PrintOperationBeginPrintCallback
cb
    FunPtr C_PrintOperationBeginPrintCallback
cb'' <- C_PrintOperationBeginPrintCallback
-> IO (FunPtr C_PrintOperationBeginPrintCallback)
mk_PrintOperationEndPrintCallback C_PrintOperationBeginPrintCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationBeginPrintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"end-print" FunPtr C_PrintOperationBeginPrintCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationEndPrint :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationEndPrintCallback -> m SignalHandlerId
afterPrintOperationEndPrint :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationBeginPrintCallback -> m SignalHandlerId
afterPrintOperationEndPrint a
obj PrintOperationBeginPrintCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationBeginPrintCallback
cb' = PrintOperationBeginPrintCallback
-> C_PrintOperationBeginPrintCallback
wrap_PrintOperationEndPrintCallback PrintOperationBeginPrintCallback
cb
    FunPtr C_PrintOperationBeginPrintCallback
cb'' <- C_PrintOperationBeginPrintCallback
-> IO (FunPtr C_PrintOperationBeginPrintCallback)
mk_PrintOperationEndPrintCallback C_PrintOperationBeginPrintCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationBeginPrintCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"end-print" FunPtr C_PrintOperationBeginPrintCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationEndPrintSignalInfo
instance SignalInfo PrintOperationEndPrintSignalInfo where
    type HaskellCallbackType PrintOperationEndPrintSignalInfo = PrintOperationEndPrintCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationEndPrintCallback cb
        cb'' <- mk_PrintOperationEndPrintCallback cb'
        connectSignalFunPtr obj "end-print" cb'' connectMode detail
#endif
type PrintOperationPaginateCallback =
    Gtk.PrintContext.PrintContext
    
    -> IO Bool
    
noPrintOperationPaginateCallback :: Maybe PrintOperationPaginateCallback
noPrintOperationPaginateCallback :: Maybe PrintOperationPaginateCallback
noPrintOperationPaginateCallback = Maybe PrintOperationPaginateCallback
forall a. Maybe a
Nothing
type C_PrintOperationPaginateCallback =
    Ptr () ->                               
    Ptr Gtk.PrintContext.PrintContext ->
    Ptr () ->                               
    IO CInt
foreign import ccall "wrapper"
    mk_PrintOperationPaginateCallback :: C_PrintOperationPaginateCallback -> IO (FunPtr C_PrintOperationPaginateCallback)
genClosure_PrintOperationPaginate :: MonadIO m => PrintOperationPaginateCallback -> m (GClosure C_PrintOperationPaginateCallback)
genClosure_PrintOperationPaginate :: forall (m :: * -> *).
MonadIO m =>
PrintOperationPaginateCallback
-> m (GClosure C_PrintOperationPaginateCallback)
genClosure_PrintOperationPaginate PrintOperationPaginateCallback
cb = IO (GClosure C_PrintOperationPaginateCallback)
-> m (GClosure C_PrintOperationPaginateCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationPaginateCallback)
 -> m (GClosure C_PrintOperationPaginateCallback))
-> IO (GClosure C_PrintOperationPaginateCallback)
-> m (GClosure C_PrintOperationPaginateCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationPaginateCallback
cb' = PrintOperationPaginateCallback -> C_PrintOperationPaginateCallback
wrap_PrintOperationPaginateCallback PrintOperationPaginateCallback
cb
    C_PrintOperationPaginateCallback
-> IO (FunPtr C_PrintOperationPaginateCallback)
mk_PrintOperationPaginateCallback C_PrintOperationPaginateCallback
cb' IO (FunPtr C_PrintOperationPaginateCallback)
-> (FunPtr C_PrintOperationPaginateCallback
    -> IO (GClosure C_PrintOperationPaginateCallback))
-> IO (GClosure C_PrintOperationPaginateCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationPaginateCallback
-> IO (GClosure C_PrintOperationPaginateCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationPaginateCallback ::
    PrintOperationPaginateCallback ->
    C_PrintOperationPaginateCallback
wrap_PrintOperationPaginateCallback :: PrintOperationPaginateCallback -> C_PrintOperationPaginateCallback
wrap_PrintOperationPaginateCallback PrintOperationPaginateCallback
_cb Ptr ()
_ Ptr PrintContext
context Ptr ()
_ = do
    PrintContext
context' <- ((ManagedPtr PrintContext -> PrintContext)
-> Ptr PrintContext -> IO PrintContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintContext -> PrintContext
Gtk.PrintContext.PrintContext) Ptr PrintContext
context
    Bool
result <- PrintOperationPaginateCallback
_cb  PrintContext
context'
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onPrintOperationPaginate :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationPaginateCallback -> m SignalHandlerId
onPrintOperationPaginate :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationPaginateCallback -> m SignalHandlerId
onPrintOperationPaginate a
obj PrintOperationPaginateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationPaginateCallback
cb' = PrintOperationPaginateCallback -> C_PrintOperationPaginateCallback
wrap_PrintOperationPaginateCallback PrintOperationPaginateCallback
cb
    FunPtr C_PrintOperationPaginateCallback
cb'' <- C_PrintOperationPaginateCallback
-> IO (FunPtr C_PrintOperationPaginateCallback)
mk_PrintOperationPaginateCallback C_PrintOperationPaginateCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationPaginateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"paginate" FunPtr C_PrintOperationPaginateCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationPaginate :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationPaginateCallback -> m SignalHandlerId
afterPrintOperationPaginate :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationPaginateCallback -> m SignalHandlerId
afterPrintOperationPaginate a
obj PrintOperationPaginateCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationPaginateCallback
cb' = PrintOperationPaginateCallback -> C_PrintOperationPaginateCallback
wrap_PrintOperationPaginateCallback PrintOperationPaginateCallback
cb
    FunPtr C_PrintOperationPaginateCallback
cb'' <- C_PrintOperationPaginateCallback
-> IO (FunPtr C_PrintOperationPaginateCallback)
mk_PrintOperationPaginateCallback C_PrintOperationPaginateCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationPaginateCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"paginate" FunPtr C_PrintOperationPaginateCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationPaginateSignalInfo
instance SignalInfo PrintOperationPaginateSignalInfo where
    type HaskellCallbackType PrintOperationPaginateSignalInfo = PrintOperationPaginateCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationPaginateCallback cb
        cb'' <- mk_PrintOperationPaginateCallback cb'
        connectSignalFunPtr obj "paginate" cb'' connectMode detail
#endif
type PrintOperationPreviewCallback =
    Gtk.PrintOperationPreview.PrintOperationPreview
    
    -> Gtk.PrintContext.PrintContext
    
    -> Maybe Gtk.Window.Window
    
    -> IO Bool
    
noPrintOperationPreviewCallback :: Maybe PrintOperationPreviewCallback
noPrintOperationPreviewCallback :: Maybe PrintOperationPreviewCallback
noPrintOperationPreviewCallback = Maybe PrintOperationPreviewCallback
forall a. Maybe a
Nothing
type C_PrintOperationPreviewCallback =
    Ptr () ->                               
    Ptr Gtk.PrintOperationPreview.PrintOperationPreview ->
    Ptr Gtk.PrintContext.PrintContext ->
    Ptr Gtk.Window.Window ->
    Ptr () ->                               
    IO CInt
foreign import ccall "wrapper"
    mk_PrintOperationPreviewCallback :: C_PrintOperationPreviewCallback -> IO (FunPtr C_PrintOperationPreviewCallback)
genClosure_PrintOperationPreview :: MonadIO m => PrintOperationPreviewCallback -> m (GClosure C_PrintOperationPreviewCallback)
genClosure_PrintOperationPreview :: forall (m :: * -> *).
MonadIO m =>
PrintOperationPreviewCallback
-> m (GClosure C_PrintOperationPreviewCallback)
genClosure_PrintOperationPreview PrintOperationPreviewCallback
cb = IO (GClosure C_PrintOperationPreviewCallback)
-> m (GClosure C_PrintOperationPreviewCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationPreviewCallback)
 -> m (GClosure C_PrintOperationPreviewCallback))
-> IO (GClosure C_PrintOperationPreviewCallback)
-> m (GClosure C_PrintOperationPreviewCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationPreviewCallback
cb' = PrintOperationPreviewCallback -> C_PrintOperationPreviewCallback
wrap_PrintOperationPreviewCallback PrintOperationPreviewCallback
cb
    C_PrintOperationPreviewCallback
-> IO (FunPtr C_PrintOperationPreviewCallback)
mk_PrintOperationPreviewCallback C_PrintOperationPreviewCallback
cb' IO (FunPtr C_PrintOperationPreviewCallback)
-> (FunPtr C_PrintOperationPreviewCallback
    -> IO (GClosure C_PrintOperationPreviewCallback))
-> IO (GClosure C_PrintOperationPreviewCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationPreviewCallback
-> IO (GClosure C_PrintOperationPreviewCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationPreviewCallback ::
    PrintOperationPreviewCallback ->
    C_PrintOperationPreviewCallback
wrap_PrintOperationPreviewCallback :: PrintOperationPreviewCallback -> C_PrintOperationPreviewCallback
wrap_PrintOperationPreviewCallback PrintOperationPreviewCallback
_cb Ptr ()
_ Ptr PrintOperationPreview
preview Ptr PrintContext
context Ptr Window
parent Ptr ()
_ = do
    PrintOperationPreview
preview' <- ((ManagedPtr PrintOperationPreview -> PrintOperationPreview)
-> Ptr PrintOperationPreview -> IO PrintOperationPreview
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintOperationPreview -> PrintOperationPreview
Gtk.PrintOperationPreview.PrintOperationPreview) Ptr PrintOperationPreview
preview
    PrintContext
context' <- ((ManagedPtr PrintContext -> PrintContext)
-> Ptr PrintContext -> IO PrintContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintContext -> PrintContext
Gtk.PrintContext.PrintContext) Ptr PrintContext
context
    Maybe Window
maybeParent <-
        if Ptr Window
parent Ptr Window -> Ptr Window -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Window
forall a. Ptr a
nullPtr
        then Maybe Window -> IO (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
forall a. Maybe a
Nothing
        else do
            Window
parent' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gtk.Window.Window) Ptr Window
parent
            Maybe Window -> IO (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Window -> IO (Maybe Window))
-> Maybe Window -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ Window -> Maybe Window
forall a. a -> Maybe a
Just Window
parent'
    Bool
result <- PrintOperationPreviewCallback
_cb  PrintOperationPreview
preview' PrintContext
context' Maybe Window
maybeParent
    let result' :: CInt
result' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
result
    CInt -> IO CInt
forall (m :: * -> *) a. Monad m => a -> m a
return CInt
result'
onPrintOperationPreview :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationPreviewCallback -> m SignalHandlerId
onPrintOperationPreview :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationPreviewCallback -> m SignalHandlerId
onPrintOperationPreview a
obj PrintOperationPreviewCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationPreviewCallback
cb' = PrintOperationPreviewCallback -> C_PrintOperationPreviewCallback
wrap_PrintOperationPreviewCallback PrintOperationPreviewCallback
cb
    FunPtr C_PrintOperationPreviewCallback
cb'' <- C_PrintOperationPreviewCallback
-> IO (FunPtr C_PrintOperationPreviewCallback)
mk_PrintOperationPreviewCallback C_PrintOperationPreviewCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationPreviewCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"preview" FunPtr C_PrintOperationPreviewCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationPreview :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationPreviewCallback -> m SignalHandlerId
afterPrintOperationPreview :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationPreviewCallback -> m SignalHandlerId
afterPrintOperationPreview a
obj PrintOperationPreviewCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationPreviewCallback
cb' = PrintOperationPreviewCallback -> C_PrintOperationPreviewCallback
wrap_PrintOperationPreviewCallback PrintOperationPreviewCallback
cb
    FunPtr C_PrintOperationPreviewCallback
cb'' <- C_PrintOperationPreviewCallback
-> IO (FunPtr C_PrintOperationPreviewCallback)
mk_PrintOperationPreviewCallback C_PrintOperationPreviewCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationPreviewCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"preview" FunPtr C_PrintOperationPreviewCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationPreviewSignalInfo
instance SignalInfo PrintOperationPreviewSignalInfo where
    type HaskellCallbackType PrintOperationPreviewSignalInfo = PrintOperationPreviewCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationPreviewCallback cb
        cb'' <- mk_PrintOperationPreviewCallback cb'
        connectSignalFunPtr obj "preview" cb'' connectMode detail
#endif
type PrintOperationRequestPageSetupCallback =
    Gtk.PrintContext.PrintContext
    
    -> Int32
    
    -> Gtk.PageSetup.PageSetup
    
    -> IO ()
noPrintOperationRequestPageSetupCallback :: Maybe PrintOperationRequestPageSetupCallback
noPrintOperationRequestPageSetupCallback :: Maybe PrintOperationRequestPageSetupCallback
noPrintOperationRequestPageSetupCallback = Maybe PrintOperationRequestPageSetupCallback
forall a. Maybe a
Nothing
type C_PrintOperationRequestPageSetupCallback =
    Ptr () ->                               
    Ptr Gtk.PrintContext.PrintContext ->
    Int32 ->
    Ptr Gtk.PageSetup.PageSetup ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_PrintOperationRequestPageSetupCallback :: C_PrintOperationRequestPageSetupCallback -> IO (FunPtr C_PrintOperationRequestPageSetupCallback)
genClosure_PrintOperationRequestPageSetup :: MonadIO m => PrintOperationRequestPageSetupCallback -> m (GClosure C_PrintOperationRequestPageSetupCallback)
genClosure_PrintOperationRequestPageSetup :: forall (m :: * -> *).
MonadIO m =>
PrintOperationRequestPageSetupCallback
-> m (GClosure C_PrintOperationRequestPageSetupCallback)
genClosure_PrintOperationRequestPageSetup PrintOperationRequestPageSetupCallback
cb = IO (GClosure C_PrintOperationRequestPageSetupCallback)
-> m (GClosure C_PrintOperationRequestPageSetupCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationRequestPageSetupCallback)
 -> m (GClosure C_PrintOperationRequestPageSetupCallback))
-> IO (GClosure C_PrintOperationRequestPageSetupCallback)
-> m (GClosure C_PrintOperationRequestPageSetupCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationRequestPageSetupCallback
cb' = PrintOperationRequestPageSetupCallback
-> C_PrintOperationRequestPageSetupCallback
wrap_PrintOperationRequestPageSetupCallback PrintOperationRequestPageSetupCallback
cb
    C_PrintOperationRequestPageSetupCallback
-> IO (FunPtr C_PrintOperationRequestPageSetupCallback)
mk_PrintOperationRequestPageSetupCallback C_PrintOperationRequestPageSetupCallback
cb' IO (FunPtr C_PrintOperationRequestPageSetupCallback)
-> (FunPtr C_PrintOperationRequestPageSetupCallback
    -> IO (GClosure C_PrintOperationRequestPageSetupCallback))
-> IO (GClosure C_PrintOperationRequestPageSetupCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationRequestPageSetupCallback
-> IO (GClosure C_PrintOperationRequestPageSetupCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationRequestPageSetupCallback ::
    PrintOperationRequestPageSetupCallback ->
    C_PrintOperationRequestPageSetupCallback
wrap_PrintOperationRequestPageSetupCallback :: PrintOperationRequestPageSetupCallback
-> C_PrintOperationRequestPageSetupCallback
wrap_PrintOperationRequestPageSetupCallback PrintOperationRequestPageSetupCallback
_cb Ptr ()
_ Ptr PrintContext
context Int32
pageNr Ptr PageSetup
setup Ptr ()
_ = do
    PrintContext
context' <- ((ManagedPtr PrintContext -> PrintContext)
-> Ptr PrintContext -> IO PrintContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintContext -> PrintContext
Gtk.PrintContext.PrintContext) Ptr PrintContext
context
    PageSetup
setup' <- ((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
setup
    PrintOperationRequestPageSetupCallback
_cb  PrintContext
context' Int32
pageNr PageSetup
setup'
onPrintOperationRequestPageSetup :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationRequestPageSetupCallback -> m SignalHandlerId
onPrintOperationRequestPageSetup :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationRequestPageSetupCallback -> m SignalHandlerId
onPrintOperationRequestPageSetup a
obj PrintOperationRequestPageSetupCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationRequestPageSetupCallback
cb' = PrintOperationRequestPageSetupCallback
-> C_PrintOperationRequestPageSetupCallback
wrap_PrintOperationRequestPageSetupCallback PrintOperationRequestPageSetupCallback
cb
    FunPtr C_PrintOperationRequestPageSetupCallback
cb'' <- C_PrintOperationRequestPageSetupCallback
-> IO (FunPtr C_PrintOperationRequestPageSetupCallback)
mk_PrintOperationRequestPageSetupCallback C_PrintOperationRequestPageSetupCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationRequestPageSetupCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-page-setup" FunPtr C_PrintOperationRequestPageSetupCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationRequestPageSetup :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationRequestPageSetupCallback -> m SignalHandlerId
afterPrintOperationRequestPageSetup :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationRequestPageSetupCallback -> m SignalHandlerId
afterPrintOperationRequestPageSetup a
obj PrintOperationRequestPageSetupCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationRequestPageSetupCallback
cb' = PrintOperationRequestPageSetupCallback
-> C_PrintOperationRequestPageSetupCallback
wrap_PrintOperationRequestPageSetupCallback PrintOperationRequestPageSetupCallback
cb
    FunPtr C_PrintOperationRequestPageSetupCallback
cb'' <- C_PrintOperationRequestPageSetupCallback
-> IO (FunPtr C_PrintOperationRequestPageSetupCallback)
mk_PrintOperationRequestPageSetupCallback C_PrintOperationRequestPageSetupCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationRequestPageSetupCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"request-page-setup" FunPtr C_PrintOperationRequestPageSetupCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationRequestPageSetupSignalInfo
instance SignalInfo PrintOperationRequestPageSetupSignalInfo where
    type HaskellCallbackType PrintOperationRequestPageSetupSignalInfo = PrintOperationRequestPageSetupCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationRequestPageSetupCallback cb
        cb'' <- mk_PrintOperationRequestPageSetupCallback cb'
        connectSignalFunPtr obj "request-page-setup" cb'' connectMode detail
#endif
type PrintOperationStatusChangedCallback =
    IO ()
noPrintOperationStatusChangedCallback :: Maybe PrintOperationStatusChangedCallback
noPrintOperationStatusChangedCallback :: Maybe (IO ())
noPrintOperationStatusChangedCallback = Maybe (IO ())
forall a. Maybe a
Nothing
type C_PrintOperationStatusChangedCallback =
    Ptr () ->                               
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_PrintOperationStatusChangedCallback :: C_PrintOperationStatusChangedCallback -> IO (FunPtr C_PrintOperationStatusChangedCallback)
genClosure_PrintOperationStatusChanged :: MonadIO m => PrintOperationStatusChangedCallback -> m (GClosure C_PrintOperationStatusChangedCallback)
genClosure_PrintOperationStatusChanged :: forall (m :: * -> *).
MonadIO m =>
IO () -> m (GClosure C_PrintOperationStatusChangedCallback)
genClosure_PrintOperationStatusChanged IO ()
cb = IO (GClosure C_PrintOperationStatusChangedCallback)
-> m (GClosure C_PrintOperationStatusChangedCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationStatusChangedCallback)
 -> m (GClosure C_PrintOperationStatusChangedCallback))
-> IO (GClosure C_PrintOperationStatusChangedCallback)
-> m (GClosure C_PrintOperationStatusChangedCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationStatusChangedCallback
cb' = IO () -> C_PrintOperationStatusChangedCallback
wrap_PrintOperationStatusChangedCallback IO ()
cb
    C_PrintOperationStatusChangedCallback
-> IO (FunPtr C_PrintOperationStatusChangedCallback)
mk_PrintOperationStatusChangedCallback C_PrintOperationStatusChangedCallback
cb' IO (FunPtr C_PrintOperationStatusChangedCallback)
-> (FunPtr C_PrintOperationStatusChangedCallback
    -> IO (GClosure C_PrintOperationStatusChangedCallback))
-> IO (GClosure C_PrintOperationStatusChangedCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationStatusChangedCallback
-> IO (GClosure C_PrintOperationStatusChangedCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationStatusChangedCallback ::
    PrintOperationStatusChangedCallback ->
    C_PrintOperationStatusChangedCallback
wrap_PrintOperationStatusChangedCallback :: IO () -> C_PrintOperationStatusChangedCallback
wrap_PrintOperationStatusChangedCallback IO ()
_cb Ptr ()
_ Ptr ()
_ = do
    IO ()
_cb 
onPrintOperationStatusChanged :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationStatusChangedCallback -> m SignalHandlerId
onPrintOperationStatusChanged :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
onPrintOperationStatusChanged a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationStatusChangedCallback
cb' = IO () -> C_PrintOperationStatusChangedCallback
wrap_PrintOperationStatusChangedCallback IO ()
cb
    FunPtr C_PrintOperationStatusChangedCallback
cb'' <- C_PrintOperationStatusChangedCallback
-> IO (FunPtr C_PrintOperationStatusChangedCallback)
mk_PrintOperationStatusChangedCallback C_PrintOperationStatusChangedCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationStatusChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"status-changed" FunPtr C_PrintOperationStatusChangedCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationStatusChanged :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationStatusChangedCallback -> m SignalHandlerId
afterPrintOperationStatusChanged :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> IO () -> m SignalHandlerId
afterPrintOperationStatusChanged a
obj IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationStatusChangedCallback
cb' = IO () -> C_PrintOperationStatusChangedCallback
wrap_PrintOperationStatusChangedCallback IO ()
cb
    FunPtr C_PrintOperationStatusChangedCallback
cb'' <- C_PrintOperationStatusChangedCallback
-> IO (FunPtr C_PrintOperationStatusChangedCallback)
mk_PrintOperationStatusChangedCallback C_PrintOperationStatusChangedCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationStatusChangedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"status-changed" FunPtr C_PrintOperationStatusChangedCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationStatusChangedSignalInfo
instance SignalInfo PrintOperationStatusChangedSignalInfo where
    type HaskellCallbackType PrintOperationStatusChangedSignalInfo = PrintOperationStatusChangedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationStatusChangedCallback cb
        cb'' <- mk_PrintOperationStatusChangedCallback cb'
        connectSignalFunPtr obj "status-changed" cb'' connectMode detail
#endif
type PrintOperationUpdateCustomWidgetCallback =
    Gtk.Widget.Widget
    
    -> Gtk.PageSetup.PageSetup
    
    -> Gtk.PrintSettings.PrintSettings
    
    -> IO ()
noPrintOperationUpdateCustomWidgetCallback :: Maybe PrintOperationUpdateCustomWidgetCallback
noPrintOperationUpdateCustomWidgetCallback :: Maybe PrintOperationUpdateCustomWidgetCallback
noPrintOperationUpdateCustomWidgetCallback = Maybe PrintOperationUpdateCustomWidgetCallback
forall a. Maybe a
Nothing
type C_PrintOperationUpdateCustomWidgetCallback =
    Ptr () ->                               
    Ptr Gtk.Widget.Widget ->
    Ptr Gtk.PageSetup.PageSetup ->
    Ptr Gtk.PrintSettings.PrintSettings ->
    Ptr () ->                               
    IO ()
foreign import ccall "wrapper"
    mk_PrintOperationUpdateCustomWidgetCallback :: C_PrintOperationUpdateCustomWidgetCallback -> IO (FunPtr C_PrintOperationUpdateCustomWidgetCallback)
genClosure_PrintOperationUpdateCustomWidget :: MonadIO m => PrintOperationUpdateCustomWidgetCallback -> m (GClosure C_PrintOperationUpdateCustomWidgetCallback)
genClosure_PrintOperationUpdateCustomWidget :: forall (m :: * -> *).
MonadIO m =>
PrintOperationUpdateCustomWidgetCallback
-> m (GClosure C_PrintOperationUpdateCustomWidgetCallback)
genClosure_PrintOperationUpdateCustomWidget PrintOperationUpdateCustomWidgetCallback
cb = IO (GClosure C_PrintOperationUpdateCustomWidgetCallback)
-> m (GClosure C_PrintOperationUpdateCustomWidgetCallback)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (GClosure C_PrintOperationUpdateCustomWidgetCallback)
 -> m (GClosure C_PrintOperationUpdateCustomWidgetCallback))
-> IO (GClosure C_PrintOperationUpdateCustomWidgetCallback)
-> m (GClosure C_PrintOperationUpdateCustomWidgetCallback)
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationUpdateCustomWidgetCallback
cb' = PrintOperationUpdateCustomWidgetCallback
-> C_PrintOperationUpdateCustomWidgetCallback
wrap_PrintOperationUpdateCustomWidgetCallback PrintOperationUpdateCustomWidgetCallback
cb
    C_PrintOperationUpdateCustomWidgetCallback
-> IO (FunPtr C_PrintOperationUpdateCustomWidgetCallback)
mk_PrintOperationUpdateCustomWidgetCallback C_PrintOperationUpdateCustomWidgetCallback
cb' IO (FunPtr C_PrintOperationUpdateCustomWidgetCallback)
-> (FunPtr C_PrintOperationUpdateCustomWidgetCallback
    -> IO (GClosure C_PrintOperationUpdateCustomWidgetCallback))
-> IO (GClosure C_PrintOperationUpdateCustomWidgetCallback)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= FunPtr C_PrintOperationUpdateCustomWidgetCallback
-> IO (GClosure C_PrintOperationUpdateCustomWidgetCallback)
forall (m :: * -> *) a. MonadIO m => FunPtr a -> m (GClosure a)
B.GClosure.newGClosure
wrap_PrintOperationUpdateCustomWidgetCallback ::
    PrintOperationUpdateCustomWidgetCallback ->
    C_PrintOperationUpdateCustomWidgetCallback
wrap_PrintOperationUpdateCustomWidgetCallback :: PrintOperationUpdateCustomWidgetCallback
-> C_PrintOperationUpdateCustomWidgetCallback
wrap_PrintOperationUpdateCustomWidgetCallback PrintOperationUpdateCustomWidgetCallback
_cb Ptr ()
_ Ptr Widget
widget Ptr PageSetup
setup Ptr PrintSettings
settings Ptr ()
_ = do
    Widget
widget' <- ((ManagedPtr Widget -> Widget) -> Ptr Widget -> IO Widget
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Widget -> Widget
Gtk.Widget.Widget) Ptr Widget
widget
    PageSetup
setup' <- ((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
setup
    PrintSettings
settings' <- ((ManagedPtr PrintSettings -> PrintSettings)
-> Ptr PrintSettings -> IO PrintSettings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintSettings -> PrintSettings
Gtk.PrintSettings.PrintSettings) Ptr PrintSettings
settings
    PrintOperationUpdateCustomWidgetCallback
_cb  Widget
widget' PageSetup
setup' PrintSettings
settings'
onPrintOperationUpdateCustomWidget :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationUpdateCustomWidgetCallback -> m SignalHandlerId
onPrintOperationUpdateCustomWidget :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationUpdateCustomWidgetCallback -> m SignalHandlerId
onPrintOperationUpdateCustomWidget a
obj PrintOperationUpdateCustomWidgetCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationUpdateCustomWidgetCallback
cb' = PrintOperationUpdateCustomWidgetCallback
-> C_PrintOperationUpdateCustomWidgetCallback
wrap_PrintOperationUpdateCustomWidgetCallback PrintOperationUpdateCustomWidgetCallback
cb
    FunPtr C_PrintOperationUpdateCustomWidgetCallback
cb'' <- C_PrintOperationUpdateCustomWidgetCallback
-> IO (FunPtr C_PrintOperationUpdateCustomWidgetCallback)
mk_PrintOperationUpdateCustomWidgetCallback C_PrintOperationUpdateCustomWidgetCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationUpdateCustomWidgetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"update-custom-widget" FunPtr C_PrintOperationUpdateCustomWidgetCallback
cb'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing
afterPrintOperationUpdateCustomWidget :: (IsPrintOperation a, MonadIO m) => a -> PrintOperationUpdateCustomWidgetCallback -> m SignalHandlerId
afterPrintOperationUpdateCustomWidget :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> PrintOperationUpdateCustomWidgetCallback -> m SignalHandlerId
afterPrintOperationUpdateCustomWidget a
obj PrintOperationUpdateCustomWidgetCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let cb' :: C_PrintOperationUpdateCustomWidgetCallback
cb' = PrintOperationUpdateCustomWidgetCallback
-> C_PrintOperationUpdateCustomWidgetCallback
wrap_PrintOperationUpdateCustomWidgetCallback PrintOperationUpdateCustomWidgetCallback
cb
    FunPtr C_PrintOperationUpdateCustomWidgetCallback
cb'' <- C_PrintOperationUpdateCustomWidgetCallback
-> IO (FunPtr C_PrintOperationUpdateCustomWidgetCallback)
mk_PrintOperationUpdateCustomWidgetCallback C_PrintOperationUpdateCustomWidgetCallback
cb'
    a
-> Text
-> FunPtr C_PrintOperationUpdateCustomWidgetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"update-custom-widget" FunPtr C_PrintOperationUpdateCustomWidgetCallback
cb'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
data PrintOperationUpdateCustomWidgetSignalInfo
instance SignalInfo PrintOperationUpdateCustomWidgetSignalInfo where
    type HaskellCallbackType PrintOperationUpdateCustomWidgetSignalInfo = PrintOperationUpdateCustomWidgetCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationUpdateCustomWidgetCallback cb
        cb'' <- mk_PrintOperationUpdateCustomWidgetCallback cb'
        connectSignalFunPtr obj "update-custom-widget" cb'' connectMode detail
#endif
   
   
   
getPrintOperationAllowAsync :: (MonadIO m, IsPrintOperation o) => o -> m Bool
getPrintOperationAllowAsync :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Bool
getPrintOperationAllowAsync o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"allow-async"
setPrintOperationAllowAsync :: (MonadIO m, IsPrintOperation o) => o -> Bool -> m ()
setPrintOperationAllowAsync :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Bool -> m ()
setPrintOperationAllowAsync o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"allow-async" Bool
val
constructPrintOperationAllowAsync :: (IsPrintOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrintOperationAllowAsync :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrintOperationAllowAsync Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"allow-async" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationAllowAsyncPropertyInfo
instance AttrInfo PrintOperationAllowAsyncPropertyInfo where
    type AttrAllowedOps PrintOperationAllowAsyncPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationAllowAsyncPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationAllowAsyncPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PrintOperationAllowAsyncPropertyInfo = (~) Bool
    type AttrTransferType PrintOperationAllowAsyncPropertyInfo = Bool
    type AttrGetType PrintOperationAllowAsyncPropertyInfo = Bool
    type AttrLabel PrintOperationAllowAsyncPropertyInfo = "allow-async"
    type AttrOrigin PrintOperationAllowAsyncPropertyInfo = PrintOperation
    attrGet = getPrintOperationAllowAsync
    attrSet = setPrintOperationAllowAsync
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationAllowAsync
    attrClear = undefined
#endif
   
   
   
getPrintOperationCurrentPage :: (MonadIO m, IsPrintOperation o) => o -> m Int32
getPrintOperationCurrentPage :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Int32
getPrintOperationCurrentPage o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"current-page"
setPrintOperationCurrentPage :: (MonadIO m, IsPrintOperation o) => o -> Int32 -> m ()
setPrintOperationCurrentPage :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Int32 -> m ()
setPrintOperationCurrentPage o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"current-page" Int32
val
constructPrintOperationCurrentPage :: (IsPrintOperation o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructPrintOperationCurrentPage :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructPrintOperationCurrentPage Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"current-page" Int32
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationCurrentPagePropertyInfo
instance AttrInfo PrintOperationCurrentPagePropertyInfo where
    type AttrAllowedOps PrintOperationCurrentPagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationCurrentPagePropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationCurrentPagePropertyInfo = (~) Int32
    type AttrTransferTypeConstraint PrintOperationCurrentPagePropertyInfo = (~) Int32
    type AttrTransferType PrintOperationCurrentPagePropertyInfo = Int32
    type AttrGetType PrintOperationCurrentPagePropertyInfo = Int32
    type AttrLabel PrintOperationCurrentPagePropertyInfo = "current-page"
    type AttrOrigin PrintOperationCurrentPagePropertyInfo = PrintOperation
    attrGet = getPrintOperationCurrentPage
    attrSet = setPrintOperationCurrentPage
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationCurrentPage
    attrClear = undefined
#endif
   
   
   
getPrintOperationCustomTabLabel :: (MonadIO m, IsPrintOperation o) => o -> m (Maybe T.Text)
getPrintOperationCustomTabLabel :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m (Maybe Text)
getPrintOperationCustomTabLabel o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"custom-tab-label"
setPrintOperationCustomTabLabel :: (MonadIO m, IsPrintOperation o) => o -> T.Text -> m ()
setPrintOperationCustomTabLabel :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Text -> m ()
setPrintOperationCustomTabLabel o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"custom-tab-label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructPrintOperationCustomTabLabel :: (IsPrintOperation o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPrintOperationCustomTabLabel :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPrintOperationCustomTabLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"custom-tab-label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearPrintOperationCustomTabLabel :: (MonadIO m, IsPrintOperation o) => o -> m ()
clearPrintOperationCustomTabLabel :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m ()
clearPrintOperationCustomTabLabel o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"custom-tab-label" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data PrintOperationCustomTabLabelPropertyInfo
instance AttrInfo PrintOperationCustomTabLabelPropertyInfo where
    type AttrAllowedOps PrintOperationCustomTabLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PrintOperationCustomTabLabelPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationCustomTabLabelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PrintOperationCustomTabLabelPropertyInfo = (~) T.Text
    type AttrTransferType PrintOperationCustomTabLabelPropertyInfo = T.Text
    type AttrGetType PrintOperationCustomTabLabelPropertyInfo = (Maybe T.Text)
    type AttrLabel PrintOperationCustomTabLabelPropertyInfo = "custom-tab-label"
    type AttrOrigin PrintOperationCustomTabLabelPropertyInfo = PrintOperation
    attrGet = getPrintOperationCustomTabLabel
    attrSet = setPrintOperationCustomTabLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationCustomTabLabel
    attrClear = clearPrintOperationCustomTabLabel
#endif
   
   
   
getPrintOperationDefaultPageSetup :: (MonadIO m, IsPrintOperation o) => o -> m Gtk.PageSetup.PageSetup
getPrintOperationDefaultPageSetup :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m PageSetup
getPrintOperationDefaultPageSetup o
obj = IO PageSetup -> m PageSetup
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PageSetup -> m PageSetup) -> IO PageSetup -> m PageSetup
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe PageSetup) -> IO PageSetup
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getPrintOperationDefaultPageSetup" (IO (Maybe PageSetup) -> IO PageSetup)
-> IO (Maybe PageSetup) -> IO PageSetup
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr PageSetup -> PageSetup)
-> IO (Maybe PageSetup)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"default-page-setup" ManagedPtr PageSetup -> PageSetup
Gtk.PageSetup.PageSetup
setPrintOperationDefaultPageSetup :: (MonadIO m, IsPrintOperation o, Gtk.PageSetup.IsPageSetup a) => o -> a -> m ()
setPrintOperationDefaultPageSetup :: forall (m :: * -> *) o a.
(MonadIO m, IsPrintOperation o, IsPageSetup a) =>
o -> a -> m ()
setPrintOperationDefaultPageSetup o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"default-page-setup" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructPrintOperationDefaultPageSetup :: (IsPrintOperation o, MIO.MonadIO m, Gtk.PageSetup.IsPageSetup a) => a -> m (GValueConstruct o)
constructPrintOperationDefaultPageSetup :: forall o (m :: * -> *) a.
(IsPrintOperation o, MonadIO m, IsPageSetup a) =>
a -> m (GValueConstruct o)
constructPrintOperationDefaultPageSetup a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"default-page-setup" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearPrintOperationDefaultPageSetup :: (MonadIO m, IsPrintOperation o) => o -> m ()
clearPrintOperationDefaultPageSetup :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m ()
clearPrintOperationDefaultPageSetup o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe PageSetup -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"default-page-setup" (Maybe PageSetup
forall a. Maybe a
Nothing :: Maybe Gtk.PageSetup.PageSetup)
#if defined(ENABLE_OVERLOADING)
data PrintOperationDefaultPageSetupPropertyInfo
instance AttrInfo PrintOperationDefaultPageSetupPropertyInfo where
    type AttrAllowedOps PrintOperationDefaultPageSetupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PrintOperationDefaultPageSetupPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationDefaultPageSetupPropertyInfo = Gtk.PageSetup.IsPageSetup
    type AttrTransferTypeConstraint PrintOperationDefaultPageSetupPropertyInfo = Gtk.PageSetup.IsPageSetup
    type AttrTransferType PrintOperationDefaultPageSetupPropertyInfo = Gtk.PageSetup.PageSetup
    type AttrGetType PrintOperationDefaultPageSetupPropertyInfo = Gtk.PageSetup.PageSetup
    type AttrLabel PrintOperationDefaultPageSetupPropertyInfo = "default-page-setup"
    type AttrOrigin PrintOperationDefaultPageSetupPropertyInfo = PrintOperation
    attrGet = getPrintOperationDefaultPageSetup
    attrSet = setPrintOperationDefaultPageSetup
    attrTransfer _ v = do
        unsafeCastTo Gtk.PageSetup.PageSetup v
    attrConstruct = constructPrintOperationDefaultPageSetup
    attrClear = clearPrintOperationDefaultPageSetup
#endif
   
   
   
getPrintOperationEmbedPageSetup :: (MonadIO m, IsPrintOperation o) => o -> m Bool
getPrintOperationEmbedPageSetup :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Bool
getPrintOperationEmbedPageSetup o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"embed-page-setup"
setPrintOperationEmbedPageSetup :: (MonadIO m, IsPrintOperation o) => o -> Bool -> m ()
setPrintOperationEmbedPageSetup :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Bool -> m ()
setPrintOperationEmbedPageSetup o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"embed-page-setup" Bool
val
constructPrintOperationEmbedPageSetup :: (IsPrintOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrintOperationEmbedPageSetup :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrintOperationEmbedPageSetup Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"embed-page-setup" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationEmbedPageSetupPropertyInfo
instance AttrInfo PrintOperationEmbedPageSetupPropertyInfo where
    type AttrAllowedOps PrintOperationEmbedPageSetupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationEmbedPageSetupPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationEmbedPageSetupPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PrintOperationEmbedPageSetupPropertyInfo = (~) Bool
    type AttrTransferType PrintOperationEmbedPageSetupPropertyInfo = Bool
    type AttrGetType PrintOperationEmbedPageSetupPropertyInfo = Bool
    type AttrLabel PrintOperationEmbedPageSetupPropertyInfo = "embed-page-setup"
    type AttrOrigin PrintOperationEmbedPageSetupPropertyInfo = PrintOperation
    attrGet = getPrintOperationEmbedPageSetup
    attrSet = setPrintOperationEmbedPageSetup
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationEmbedPageSetup
    attrClear = undefined
#endif
   
   
   
getPrintOperationExportFilename :: (MonadIO m, IsPrintOperation o) => o -> m (Maybe T.Text)
getPrintOperationExportFilename :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m (Maybe Text)
getPrintOperationExportFilename o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"export-filename"
setPrintOperationExportFilename :: (MonadIO m, IsPrintOperation o) => o -> T.Text -> m ()
setPrintOperationExportFilename :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Text -> m ()
setPrintOperationExportFilename o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"export-filename" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructPrintOperationExportFilename :: (IsPrintOperation o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPrintOperationExportFilename :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPrintOperationExportFilename Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"export-filename" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
clearPrintOperationExportFilename :: (MonadIO m, IsPrintOperation o) => o -> m ()
clearPrintOperationExportFilename :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m ()
clearPrintOperationExportFilename o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"export-filename" (Maybe Text
forall a. Maybe a
Nothing :: Maybe T.Text)
#if defined(ENABLE_OVERLOADING)
data PrintOperationExportFilenamePropertyInfo
instance AttrInfo PrintOperationExportFilenamePropertyInfo where
    type AttrAllowedOps PrintOperationExportFilenamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PrintOperationExportFilenamePropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationExportFilenamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PrintOperationExportFilenamePropertyInfo = (~) T.Text
    type AttrTransferType PrintOperationExportFilenamePropertyInfo = T.Text
    type AttrGetType PrintOperationExportFilenamePropertyInfo = (Maybe T.Text)
    type AttrLabel PrintOperationExportFilenamePropertyInfo = "export-filename"
    type AttrOrigin PrintOperationExportFilenamePropertyInfo = PrintOperation
    attrGet = getPrintOperationExportFilename
    attrSet = setPrintOperationExportFilename
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationExportFilename
    attrClear = clearPrintOperationExportFilename
#endif
   
   
   
getPrintOperationHasSelection :: (MonadIO m, IsPrintOperation o) => o -> m Bool
getPrintOperationHasSelection :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Bool
getPrintOperationHasSelection o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"has-selection"
setPrintOperationHasSelection :: (MonadIO m, IsPrintOperation o) => o -> Bool -> m ()
setPrintOperationHasSelection :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Bool -> m ()
setPrintOperationHasSelection o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"has-selection" Bool
val
constructPrintOperationHasSelection :: (IsPrintOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrintOperationHasSelection :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrintOperationHasSelection Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"has-selection" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationHasSelectionPropertyInfo
instance AttrInfo PrintOperationHasSelectionPropertyInfo where
    type AttrAllowedOps PrintOperationHasSelectionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationHasSelectionPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationHasSelectionPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PrintOperationHasSelectionPropertyInfo = (~) Bool
    type AttrTransferType PrintOperationHasSelectionPropertyInfo = Bool
    type AttrGetType PrintOperationHasSelectionPropertyInfo = Bool
    type AttrLabel PrintOperationHasSelectionPropertyInfo = "has-selection"
    type AttrOrigin PrintOperationHasSelectionPropertyInfo = PrintOperation
    attrGet = getPrintOperationHasSelection
    attrSet = setPrintOperationHasSelection
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationHasSelection
    attrClear = undefined
#endif
   
   
   
getPrintOperationJobName :: (MonadIO m, IsPrintOperation o) => o -> m (Maybe T.Text)
getPrintOperationJobName :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m (Maybe Text)
getPrintOperationJobName o
obj = IO (Maybe Text) -> m (Maybe Text)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Text) -> m (Maybe Text))
-> IO (Maybe Text) -> m (Maybe Text)
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"job-name"
setPrintOperationJobName :: (MonadIO m, IsPrintOperation o) => o -> T.Text -> m ()
setPrintOperationJobName :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Text -> m ()
setPrintOperationJobName o
obj Text
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe Text -> IO ()
forall a. GObject a => a -> String -> Maybe Text -> IO ()
B.Properties.setObjectPropertyString o
obj String
"job-name" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)
constructPrintOperationJobName :: (IsPrintOperation o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPrintOperationJobName :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPrintOperationJobName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"job-name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data PrintOperationJobNamePropertyInfo
instance AttrInfo PrintOperationJobNamePropertyInfo where
    type AttrAllowedOps PrintOperationJobNamePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationJobNamePropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationJobNamePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PrintOperationJobNamePropertyInfo = (~) T.Text
    type AttrTransferType PrintOperationJobNamePropertyInfo = T.Text
    type AttrGetType PrintOperationJobNamePropertyInfo = (Maybe T.Text)
    type AttrLabel PrintOperationJobNamePropertyInfo = "job-name"
    type AttrOrigin PrintOperationJobNamePropertyInfo = PrintOperation
    attrGet = getPrintOperationJobName
    attrSet = setPrintOperationJobName
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationJobName
    attrClear = undefined
#endif
   
   
   
getPrintOperationNPages :: (MonadIO m, IsPrintOperation o) => o -> m Int32
getPrintOperationNPages :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Int32
getPrintOperationNPages o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"n-pages"
setPrintOperationNPages :: (MonadIO m, IsPrintOperation o) => o -> Int32 -> m ()
setPrintOperationNPages :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Int32 -> m ()
setPrintOperationNPages o
obj Int32
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Int32 -> IO ()
forall a. GObject a => a -> String -> Int32 -> IO ()
B.Properties.setObjectPropertyInt32 o
obj String
"n-pages" Int32
val
constructPrintOperationNPages :: (IsPrintOperation o, MIO.MonadIO m) => Int32 -> m (GValueConstruct o)
constructPrintOperationNPages :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Int32 -> m (GValueConstruct o)
constructPrintOperationNPages Int32
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Int32 -> IO (GValueConstruct o)
forall o. String -> Int32 -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyInt32 String
"n-pages" Int32
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationNPagesPropertyInfo
instance AttrInfo PrintOperationNPagesPropertyInfo where
    type AttrAllowedOps PrintOperationNPagesPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationNPagesPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationNPagesPropertyInfo = (~) Int32
    type AttrTransferTypeConstraint PrintOperationNPagesPropertyInfo = (~) Int32
    type AttrTransferType PrintOperationNPagesPropertyInfo = Int32
    type AttrGetType PrintOperationNPagesPropertyInfo = Int32
    type AttrLabel PrintOperationNPagesPropertyInfo = "n-pages"
    type AttrOrigin PrintOperationNPagesPropertyInfo = PrintOperation
    attrGet = getPrintOperationNPages
    attrSet = setPrintOperationNPages
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationNPages
    attrClear = undefined
#endif
   
   
   
getPrintOperationNPagesToPrint :: (MonadIO m, IsPrintOperation o) => o -> m Int32
getPrintOperationNPagesToPrint :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Int32
getPrintOperationNPagesToPrint o
obj = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"n-pages-to-print"
#if defined(ENABLE_OVERLOADING)
data PrintOperationNPagesToPrintPropertyInfo
instance AttrInfo PrintOperationNPagesToPrintPropertyInfo where
    type AttrAllowedOps PrintOperationNPagesToPrintPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationNPagesToPrintPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationNPagesToPrintPropertyInfo = (~) ()
    type AttrTransferTypeConstraint PrintOperationNPagesToPrintPropertyInfo = (~) ()
    type AttrTransferType PrintOperationNPagesToPrintPropertyInfo = ()
    type AttrGetType PrintOperationNPagesToPrintPropertyInfo = Int32
    type AttrLabel PrintOperationNPagesToPrintPropertyInfo = "n-pages-to-print"
    type AttrOrigin PrintOperationNPagesToPrintPropertyInfo = PrintOperation
    attrGet = getPrintOperationNPagesToPrint
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
   
   
   
getPrintOperationPrintSettings :: (MonadIO m, IsPrintOperation o) => o -> m Gtk.PrintSettings.PrintSettings
getPrintOperationPrintSettings :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m PrintSettings
getPrintOperationPrintSettings o
obj = IO PrintSettings -> m PrintSettings
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PrintSettings -> m PrintSettings)
-> IO PrintSettings -> m PrintSettings
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe PrintSettings) -> IO PrintSettings
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getPrintOperationPrintSettings" (IO (Maybe PrintSettings) -> IO PrintSettings)
-> IO (Maybe PrintSettings) -> IO PrintSettings
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr PrintSettings -> PrintSettings)
-> IO (Maybe PrintSettings)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"print-settings" ManagedPtr PrintSettings -> PrintSettings
Gtk.PrintSettings.PrintSettings
setPrintOperationPrintSettings :: (MonadIO m, IsPrintOperation o, Gtk.PrintSettings.IsPrintSettings a) => o -> a -> m ()
setPrintOperationPrintSettings :: forall (m :: * -> *) o a.
(MonadIO m, IsPrintOperation o, IsPrintSettings a) =>
o -> a -> m ()
setPrintOperationPrintSettings o
obj a
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Maybe a -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"print-settings" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
constructPrintOperationPrintSettings :: (IsPrintOperation o, MIO.MonadIO m, Gtk.PrintSettings.IsPrintSettings a) => a -> m (GValueConstruct o)
constructPrintOperationPrintSettings :: forall o (m :: * -> *) a.
(IsPrintOperation o, MonadIO m, IsPrintSettings a) =>
a -> m (GValueConstruct o)
constructPrintOperationPrintSettings a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"print-settings" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
clearPrintOperationPrintSettings :: (MonadIO m, IsPrintOperation o) => o -> m ()
clearPrintOperationPrintSettings :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m ()
clearPrintOperationPrintSettings o
obj = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ o -> String -> Maybe PrintSettings -> IO ()
forall a b.
(GObject a, GObject b) =>
a -> String -> Maybe b -> IO ()
B.Properties.setObjectPropertyObject o
obj String
"print-settings" (Maybe PrintSettings
forall a. Maybe a
Nothing :: Maybe Gtk.PrintSettings.PrintSettings)
#if defined(ENABLE_OVERLOADING)
data PrintOperationPrintSettingsPropertyInfo
instance AttrInfo PrintOperationPrintSettingsPropertyInfo where
    type AttrAllowedOps PrintOperationPrintSettingsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PrintOperationPrintSettingsPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationPrintSettingsPropertyInfo = Gtk.PrintSettings.IsPrintSettings
    type AttrTransferTypeConstraint PrintOperationPrintSettingsPropertyInfo = Gtk.PrintSettings.IsPrintSettings
    type AttrTransferType PrintOperationPrintSettingsPropertyInfo = Gtk.PrintSettings.PrintSettings
    type AttrGetType PrintOperationPrintSettingsPropertyInfo = Gtk.PrintSettings.PrintSettings
    type AttrLabel PrintOperationPrintSettingsPropertyInfo = "print-settings"
    type AttrOrigin PrintOperationPrintSettingsPropertyInfo = PrintOperation
    attrGet = getPrintOperationPrintSettings
    attrSet = setPrintOperationPrintSettings
    attrTransfer _ v = do
        unsafeCastTo Gtk.PrintSettings.PrintSettings v
    attrConstruct = constructPrintOperationPrintSettings
    attrClear = clearPrintOperationPrintSettings
#endif
   
   
   
getPrintOperationShowProgress :: (MonadIO m, IsPrintOperation o) => o -> m Bool
getPrintOperationShowProgress :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Bool
getPrintOperationShowProgress o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"show-progress"
setPrintOperationShowProgress :: (MonadIO m, IsPrintOperation o) => o -> Bool -> m ()
setPrintOperationShowProgress :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Bool -> m ()
setPrintOperationShowProgress o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"show-progress" Bool
val
constructPrintOperationShowProgress :: (IsPrintOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrintOperationShowProgress :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrintOperationShowProgress Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"show-progress" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationShowProgressPropertyInfo
instance AttrInfo PrintOperationShowProgressPropertyInfo where
    type AttrAllowedOps PrintOperationShowProgressPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationShowProgressPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationShowProgressPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PrintOperationShowProgressPropertyInfo = (~) Bool
    type AttrTransferType PrintOperationShowProgressPropertyInfo = Bool
    type AttrGetType PrintOperationShowProgressPropertyInfo = Bool
    type AttrLabel PrintOperationShowProgressPropertyInfo = "show-progress"
    type AttrOrigin PrintOperationShowProgressPropertyInfo = PrintOperation
    attrGet = getPrintOperationShowProgress
    attrSet = setPrintOperationShowProgress
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationShowProgress
    attrClear = undefined
#endif
   
   
   
getPrintOperationStatus :: (MonadIO m, IsPrintOperation o) => o -> m Gtk.Enums.PrintStatus
getPrintOperationStatus :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m PrintStatus
getPrintOperationStatus o
obj = IO PrintStatus -> m PrintStatus
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO PrintStatus -> m PrintStatus)
-> IO PrintStatus -> m PrintStatus
forall a b. (a -> b) -> a -> b
$ o -> String -> IO PrintStatus
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"status"
#if defined(ENABLE_OVERLOADING)
data PrintOperationStatusPropertyInfo
instance AttrInfo PrintOperationStatusPropertyInfo where
    type AttrAllowedOps PrintOperationStatusPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationStatusPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationStatusPropertyInfo = (~) ()
    type AttrTransferTypeConstraint PrintOperationStatusPropertyInfo = (~) ()
    type AttrTransferType PrintOperationStatusPropertyInfo = ()
    type AttrGetType PrintOperationStatusPropertyInfo = Gtk.Enums.PrintStatus
    type AttrLabel PrintOperationStatusPropertyInfo = "status"
    type AttrOrigin PrintOperationStatusPropertyInfo = PrintOperation
    attrGet = getPrintOperationStatus
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
   
   
   
getPrintOperationStatusString :: (MonadIO m, IsPrintOperation o) => o -> m T.Text
getPrintOperationStatusString :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Text
getPrintOperationStatusString o
obj = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getPrintOperationStatusString" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"status-string"
#if defined(ENABLE_OVERLOADING)
data PrintOperationStatusStringPropertyInfo
instance AttrInfo PrintOperationStatusStringPropertyInfo where
    type AttrAllowedOps PrintOperationStatusStringPropertyInfo = '[ 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PrintOperationStatusStringPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationStatusStringPropertyInfo = (~) ()
    type AttrTransferTypeConstraint PrintOperationStatusStringPropertyInfo = (~) ()
    type AttrTransferType PrintOperationStatusStringPropertyInfo = ()
    type AttrGetType PrintOperationStatusStringPropertyInfo = T.Text
    type AttrLabel PrintOperationStatusStringPropertyInfo = "status-string"
    type AttrOrigin PrintOperationStatusStringPropertyInfo = PrintOperation
    attrGet = getPrintOperationStatusString
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
#endif
   
   
   
getPrintOperationSupportSelection :: (MonadIO m, IsPrintOperation o) => o -> m Bool
getPrintOperationSupportSelection :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Bool
getPrintOperationSupportSelection o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"support-selection"
setPrintOperationSupportSelection :: (MonadIO m, IsPrintOperation o) => o -> Bool -> m ()
setPrintOperationSupportSelection :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Bool -> m ()
setPrintOperationSupportSelection o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"support-selection" Bool
val
constructPrintOperationSupportSelection :: (IsPrintOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrintOperationSupportSelection :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrintOperationSupportSelection Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"support-selection" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationSupportSelectionPropertyInfo
instance AttrInfo PrintOperationSupportSelectionPropertyInfo where
    type AttrAllowedOps PrintOperationSupportSelectionPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationSupportSelectionPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationSupportSelectionPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PrintOperationSupportSelectionPropertyInfo = (~) Bool
    type AttrTransferType PrintOperationSupportSelectionPropertyInfo = Bool
    type AttrGetType PrintOperationSupportSelectionPropertyInfo = Bool
    type AttrLabel PrintOperationSupportSelectionPropertyInfo = "support-selection"
    type AttrOrigin PrintOperationSupportSelectionPropertyInfo = PrintOperation
    attrGet = getPrintOperationSupportSelection
    attrSet = setPrintOperationSupportSelection
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationSupportSelection
    attrClear = undefined
#endif
   
   
   
getPrintOperationTrackPrintStatus :: (MonadIO m, IsPrintOperation o) => o -> m Bool
getPrintOperationTrackPrintStatus :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Bool
getPrintOperationTrackPrintStatus o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"track-print-status"
setPrintOperationTrackPrintStatus :: (MonadIO m, IsPrintOperation o) => o -> Bool -> m ()
setPrintOperationTrackPrintStatus :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Bool -> m ()
setPrintOperationTrackPrintStatus o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"track-print-status" Bool
val
constructPrintOperationTrackPrintStatus :: (IsPrintOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrintOperationTrackPrintStatus :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrintOperationTrackPrintStatus Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"track-print-status" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationTrackPrintStatusPropertyInfo
instance AttrInfo PrintOperationTrackPrintStatusPropertyInfo where
    type AttrAllowedOps PrintOperationTrackPrintStatusPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationTrackPrintStatusPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationTrackPrintStatusPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PrintOperationTrackPrintStatusPropertyInfo = (~) Bool
    type AttrTransferType PrintOperationTrackPrintStatusPropertyInfo = Bool
    type AttrGetType PrintOperationTrackPrintStatusPropertyInfo = Bool
    type AttrLabel PrintOperationTrackPrintStatusPropertyInfo = "track-print-status"
    type AttrOrigin PrintOperationTrackPrintStatusPropertyInfo = PrintOperation
    attrGet = getPrintOperationTrackPrintStatus
    attrSet = setPrintOperationTrackPrintStatus
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationTrackPrintStatus
    attrClear = undefined
#endif
   
   
   
getPrintOperationUnit :: (MonadIO m, IsPrintOperation o) => o -> m Gtk.Enums.Unit
getPrintOperationUnit :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Unit
getPrintOperationUnit o
obj = IO Unit -> m Unit
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Unit -> m Unit) -> IO Unit -> m Unit
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Unit
forall a b. (GObject a, Enum b, BoxedEnum b) => a -> String -> IO b
B.Properties.getObjectPropertyEnum o
obj String
"unit"
setPrintOperationUnit :: (MonadIO m, IsPrintOperation o) => o -> Gtk.Enums.Unit -> m ()
setPrintOperationUnit :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Unit -> m ()
setPrintOperationUnit o
obj Unit
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Unit -> IO ()
forall a b.
(GObject a, Enum b, BoxedEnum b) =>
a -> String -> b -> IO ()
B.Properties.setObjectPropertyEnum o
obj String
"unit" Unit
val
constructPrintOperationUnit :: (IsPrintOperation o, MIO.MonadIO m) => Gtk.Enums.Unit -> m (GValueConstruct o)
constructPrintOperationUnit :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Unit -> m (GValueConstruct o)
constructPrintOperationUnit Unit
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Unit -> IO (GValueConstruct o)
forall a o.
(Enum a, BoxedEnum a) =>
String -> a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyEnum String
"unit" Unit
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationUnitPropertyInfo
instance AttrInfo PrintOperationUnitPropertyInfo where
    type AttrAllowedOps PrintOperationUnitPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationUnitPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationUnitPropertyInfo = (~) Gtk.Enums.Unit
    type AttrTransferTypeConstraint PrintOperationUnitPropertyInfo = (~) Gtk.Enums.Unit
    type AttrTransferType PrintOperationUnitPropertyInfo = Gtk.Enums.Unit
    type AttrGetType PrintOperationUnitPropertyInfo = Gtk.Enums.Unit
    type AttrLabel PrintOperationUnitPropertyInfo = "unit"
    type AttrOrigin PrintOperationUnitPropertyInfo = PrintOperation
    attrGet = getPrintOperationUnit
    attrSet = setPrintOperationUnit
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationUnit
    attrClear = undefined
#endif
   
   
   
getPrintOperationUseFullPage :: (MonadIO m, IsPrintOperation o) => o -> m Bool
getPrintOperationUseFullPage :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m Bool
getPrintOperationUseFullPage o
obj = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"use-full-page"
setPrintOperationUseFullPage :: (MonadIO m, IsPrintOperation o) => o -> Bool -> m ()
setPrintOperationUseFullPage :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> Bool -> m ()
setPrintOperationUseFullPage o
obj Bool
val = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> Bool -> IO ()
forall a. GObject a => a -> String -> Bool -> IO ()
B.Properties.setObjectPropertyBool o
obj String
"use-full-page" Bool
val
constructPrintOperationUseFullPage :: (IsPrintOperation o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrintOperationUseFullPage :: forall o (m :: * -> *).
(IsPrintOperation o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrintOperationUseFullPage Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
    IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"use-full-page" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrintOperationUseFullPagePropertyInfo
instance AttrInfo PrintOperationUseFullPagePropertyInfo where
    type AttrAllowedOps PrintOperationUseFullPagePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationUseFullPagePropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationUseFullPagePropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PrintOperationUseFullPagePropertyInfo = (~) Bool
    type AttrTransferType PrintOperationUseFullPagePropertyInfo = Bool
    type AttrGetType PrintOperationUseFullPagePropertyInfo = Bool
    type AttrLabel PrintOperationUseFullPagePropertyInfo = "use-full-page"
    type AttrOrigin PrintOperationUseFullPagePropertyInfo = PrintOperation
    attrGet = getPrintOperationUseFullPage
    attrSet = setPrintOperationUseFullPage
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintOperationUseFullPage
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PrintOperation
type instance O.AttributeList PrintOperation = PrintOperationAttributeList
type PrintOperationAttributeList = ('[ '("allowAsync", PrintOperationAllowAsyncPropertyInfo), '("currentPage", PrintOperationCurrentPagePropertyInfo), '("customTabLabel", PrintOperationCustomTabLabelPropertyInfo), '("defaultPageSetup", PrintOperationDefaultPageSetupPropertyInfo), '("embedPageSetup", PrintOperationEmbedPageSetupPropertyInfo), '("exportFilename", PrintOperationExportFilenamePropertyInfo), '("hasSelection", PrintOperationHasSelectionPropertyInfo), '("jobName", PrintOperationJobNamePropertyInfo), '("nPages", PrintOperationNPagesPropertyInfo), '("nPagesToPrint", PrintOperationNPagesToPrintPropertyInfo), '("printSettings", PrintOperationPrintSettingsPropertyInfo), '("showProgress", PrintOperationShowProgressPropertyInfo), '("status", PrintOperationStatusPropertyInfo), '("statusString", PrintOperationStatusStringPropertyInfo), '("supportSelection", PrintOperationSupportSelectionPropertyInfo), '("trackPrintStatus", PrintOperationTrackPrintStatusPropertyInfo), '("unit", PrintOperationUnitPropertyInfo), '("useFullPage", PrintOperationUseFullPagePropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
printOperationAllowAsync :: AttrLabelProxy "allowAsync"
printOperationAllowAsync = AttrLabelProxy
printOperationCurrentPage :: AttrLabelProxy "currentPage"
printOperationCurrentPage = AttrLabelProxy
printOperationCustomTabLabel :: AttrLabelProxy "customTabLabel"
printOperationCustomTabLabel = AttrLabelProxy
printOperationDefaultPageSetup :: AttrLabelProxy "defaultPageSetup"
printOperationDefaultPageSetup = AttrLabelProxy
printOperationEmbedPageSetup :: AttrLabelProxy "embedPageSetup"
printOperationEmbedPageSetup = AttrLabelProxy
printOperationExportFilename :: AttrLabelProxy "exportFilename"
printOperationExportFilename = AttrLabelProxy
printOperationHasSelection :: AttrLabelProxy "hasSelection"
printOperationHasSelection = AttrLabelProxy
printOperationJobName :: AttrLabelProxy "jobName"
printOperationJobName = AttrLabelProxy
printOperationNPages :: AttrLabelProxy "nPages"
printOperationNPages = AttrLabelProxy
printOperationNPagesToPrint :: AttrLabelProxy "nPagesToPrint"
printOperationNPagesToPrint = AttrLabelProxy
printOperationPrintSettings :: AttrLabelProxy "printSettings"
printOperationPrintSettings = AttrLabelProxy
printOperationShowProgress :: AttrLabelProxy "showProgress"
printOperationShowProgress = AttrLabelProxy
printOperationStatus :: AttrLabelProxy "status"
printOperationStatus = AttrLabelProxy
printOperationStatusString :: AttrLabelProxy "statusString"
printOperationStatusString = AttrLabelProxy
printOperationSupportSelection :: AttrLabelProxy "supportSelection"
printOperationSupportSelection = AttrLabelProxy
printOperationTrackPrintStatus :: AttrLabelProxy "trackPrintStatus"
printOperationTrackPrintStatus = AttrLabelProxy
printOperationUnit :: AttrLabelProxy "unit"
printOperationUnit = AttrLabelProxy
printOperationUseFullPage :: AttrLabelProxy "useFullPage"
printOperationUseFullPage = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PrintOperation = PrintOperationSignalList
type PrintOperationSignalList = ('[ '("beginPrint", PrintOperationBeginPrintSignalInfo), '("createCustomWidget", PrintOperationCreateCustomWidgetSignalInfo), '("customWidgetApply", PrintOperationCustomWidgetApplySignalInfo), '("done", PrintOperationDoneSignalInfo), '("drawPage", PrintOperationDrawPageSignalInfo), '("endPrint", PrintOperationEndPrintSignalInfo), '("gotPageSize", Gtk.PrintOperationPreview.PrintOperationPreviewGotPageSizeSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("paginate", PrintOperationPaginateSignalInfo), '("preview", PrintOperationPreviewSignalInfo), '("ready", Gtk.PrintOperationPreview.PrintOperationPreviewReadySignalInfo), '("requestPageSetup", PrintOperationRequestPageSetupSignalInfo), '("statusChanged", PrintOperationStatusChangedSignalInfo), '("updateCustomWidget", PrintOperationUpdateCustomWidgetSignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gtk_print_operation_new" gtk_print_operation_new :: 
    IO (Ptr PrintOperation)
printOperationNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m PrintOperation
    
printOperationNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m PrintOperation
printOperationNew  = IO PrintOperation -> m PrintOperation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintOperation -> m PrintOperation)
-> IO PrintOperation -> m PrintOperation
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
result <- IO (Ptr PrintOperation)
gtk_print_operation_new
    Text -> Ptr PrintOperation -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printOperationNew" Ptr PrintOperation
result
    PrintOperation
result' <- ((ManagedPtr PrintOperation -> PrintOperation)
-> Ptr PrintOperation -> IO PrintOperation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PrintOperation -> PrintOperation
PrintOperation) Ptr PrintOperation
result
    PrintOperation -> IO PrintOperation
forall (m :: * -> *) a. Monad m => a -> m a
return PrintOperation
result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_print_operation_cancel" gtk_print_operation_cancel :: 
    Ptr PrintOperation ->                   
    IO ()
printOperationCancel ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m ()
printOperationCancel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m ()
printOperationCancel a
op = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr PrintOperation -> IO ()
gtk_print_operation_cancel Ptr PrintOperation
op'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationCancelMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationCancelMethodInfo a signature where
    overloadedMethod = printOperationCancel
instance O.OverloadedMethodInfo PrintOperationCancelMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationCancel",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationCancel"
        }
#endif
foreign import ccall "gtk_print_operation_draw_page_finish" gtk_print_operation_draw_page_finish :: 
    Ptr PrintOperation ->                   
    IO ()
printOperationDrawPageFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m ()
printOperationDrawPageFinish :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m ()
printOperationDrawPageFinish a
op = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr PrintOperation -> IO ()
gtk_print_operation_draw_page_finish Ptr PrintOperation
op'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationDrawPageFinishMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationDrawPageFinishMethodInfo a signature where
    overloadedMethod = printOperationDrawPageFinish
instance O.OverloadedMethodInfo PrintOperationDrawPageFinishMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationDrawPageFinish",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationDrawPageFinish"
        }
#endif
foreign import ccall "gtk_print_operation_get_default_page_setup" gtk_print_operation_get_default_page_setup :: 
    Ptr PrintOperation ->                   
    IO (Ptr Gtk.PageSetup.PageSetup)
printOperationGetDefaultPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m Gtk.PageSetup.PageSetup
    
printOperationGetDefaultPageSetup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m PageSetup
printOperationGetDefaultPageSetup a
op = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr PageSetup
result <- Ptr PrintOperation -> IO (Ptr PageSetup)
gtk_print_operation_get_default_page_setup Ptr PrintOperation
op'
    Text -> Ptr PageSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printOperationGetDefaultPageSetup" 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
op
    PageSetup -> IO PageSetup
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetDefaultPageSetupMethodInfo
instance (signature ~ (m Gtk.PageSetup.PageSetup), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetDefaultPageSetupMethodInfo a signature where
    overloadedMethod = printOperationGetDefaultPageSetup
instance O.OverloadedMethodInfo PrintOperationGetDefaultPageSetupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationGetDefaultPageSetup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationGetDefaultPageSetup"
        }
#endif
foreign import ccall "gtk_print_operation_get_embed_page_setup" gtk_print_operation_get_embed_page_setup :: 
    Ptr PrintOperation ->                   
    IO CInt
printOperationGetEmbedPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m Bool
    
printOperationGetEmbedPageSetup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m Bool
printOperationGetEmbedPageSetup a
op = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CInt
result <- Ptr PrintOperation -> IO CInt
gtk_print_operation_get_embed_page_setup Ptr PrintOperation
op'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetEmbedPageSetupMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetEmbedPageSetupMethodInfo a signature where
    overloadedMethod = printOperationGetEmbedPageSetup
instance O.OverloadedMethodInfo PrintOperationGetEmbedPageSetupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationGetEmbedPageSetup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationGetEmbedPageSetup"
        }
#endif
foreign import ccall "gtk_print_operation_get_error" gtk_print_operation_get_error :: 
    Ptr PrintOperation ->                   
    Ptr (Ptr GError) ->                     
    IO ()
printOperationGetError ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m ()
    
printOperationGetError :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m ()
printOperationGetError a
op = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO ()) -> IO ())
-> (Ptr (Ptr GError) -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr PrintOperation -> Ptr (Ptr GError) -> IO ()
gtk_print_operation_get_error Ptr PrintOperation
op'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetErrorMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetErrorMethodInfo a signature where
    overloadedMethod = printOperationGetError
instance O.OverloadedMethodInfo PrintOperationGetErrorMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationGetError",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationGetError"
        }
#endif
foreign import ccall "gtk_print_operation_get_has_selection" gtk_print_operation_get_has_selection :: 
    Ptr PrintOperation ->                   
    IO CInt
printOperationGetHasSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m Bool
    
printOperationGetHasSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m Bool
printOperationGetHasSelection a
op = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CInt
result <- Ptr PrintOperation -> IO CInt
gtk_print_operation_get_has_selection Ptr PrintOperation
op'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetHasSelectionMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetHasSelectionMethodInfo a signature where
    overloadedMethod = printOperationGetHasSelection
instance O.OverloadedMethodInfo PrintOperationGetHasSelectionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationGetHasSelection",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationGetHasSelection"
        }
#endif
foreign import ccall "gtk_print_operation_get_n_pages_to_print" gtk_print_operation_get_n_pages_to_print :: 
    Ptr PrintOperation ->                   
    IO Int32
printOperationGetNPagesToPrint ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m Int32
    
printOperationGetNPagesToPrint :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m Int32
printOperationGetNPagesToPrint a
op = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Int32
result <- Ptr PrintOperation -> IO Int32
gtk_print_operation_get_n_pages_to_print Ptr PrintOperation
op'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetNPagesToPrintMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetNPagesToPrintMethodInfo a signature where
    overloadedMethod = printOperationGetNPagesToPrint
instance O.OverloadedMethodInfo PrintOperationGetNPagesToPrintMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationGetNPagesToPrint",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationGetNPagesToPrint"
        }
#endif
foreign import ccall "gtk_print_operation_get_print_settings" gtk_print_operation_get_print_settings :: 
    Ptr PrintOperation ->                   
    IO (Ptr Gtk.PrintSettings.PrintSettings)
printOperationGetPrintSettings ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m Gtk.PrintSettings.PrintSettings
    
printOperationGetPrintSettings :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m PrintSettings
printOperationGetPrintSettings a
op = IO PrintSettings -> m PrintSettings
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintSettings -> m PrintSettings)
-> IO PrintSettings -> m PrintSettings
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr PrintSettings
result <- Ptr PrintOperation -> IO (Ptr PrintSettings)
gtk_print_operation_get_print_settings Ptr PrintOperation
op'
    Text -> Ptr PrintSettings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printOperationGetPrintSettings" Ptr PrintSettings
result
    PrintSettings
result' <- ((ManagedPtr PrintSettings -> PrintSettings)
-> Ptr PrintSettings -> IO PrintSettings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintSettings -> PrintSettings
Gtk.PrintSettings.PrintSettings) Ptr PrintSettings
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    PrintSettings -> IO PrintSettings
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetPrintSettingsMethodInfo
instance (signature ~ (m Gtk.PrintSettings.PrintSettings), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetPrintSettingsMethodInfo a signature where
    overloadedMethod = printOperationGetPrintSettings
instance O.OverloadedMethodInfo PrintOperationGetPrintSettingsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationGetPrintSettings",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationGetPrintSettings"
        }
#endif
foreign import ccall "gtk_print_operation_get_status" gtk_print_operation_get_status :: 
    Ptr PrintOperation ->                   
    IO CUInt
printOperationGetStatus ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m Gtk.Enums.PrintStatus
    
printOperationGetStatus :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m PrintStatus
printOperationGetStatus a
op = IO PrintStatus -> m PrintStatus
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintStatus -> m PrintStatus)
-> IO PrintStatus -> m PrintStatus
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CUInt
result <- Ptr PrintOperation -> IO CUInt
gtk_print_operation_get_status Ptr PrintOperation
op'
    let result' :: PrintStatus
result' = (Int -> PrintStatus
forall a. Enum a => Int -> a
toEnum (Int -> PrintStatus) -> (CUInt -> Int) -> CUInt -> PrintStatus
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    PrintStatus -> IO PrintStatus
forall (m :: * -> *) a. Monad m => a -> m a
return PrintStatus
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetStatusMethodInfo
instance (signature ~ (m Gtk.Enums.PrintStatus), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetStatusMethodInfo a signature where
    overloadedMethod = printOperationGetStatus
instance O.OverloadedMethodInfo PrintOperationGetStatusMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationGetStatus",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationGetStatus"
        }
#endif
foreign import ccall "gtk_print_operation_get_status_string" gtk_print_operation_get_status_string :: 
    Ptr PrintOperation ->                   
    IO CString
printOperationGetStatusString ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m T.Text
    
    
printOperationGetStatusString :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m Text
printOperationGetStatusString a
op = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
result <- Ptr PrintOperation -> IO CString
gtk_print_operation_get_status_string Ptr PrintOperation
op'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printOperationGetStatusString" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetStatusStringMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetStatusStringMethodInfo a signature where
    overloadedMethod = printOperationGetStatusString
instance O.OverloadedMethodInfo PrintOperationGetStatusStringMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationGetStatusString",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationGetStatusString"
        }
#endif
foreign import ccall "gtk_print_operation_get_support_selection" gtk_print_operation_get_support_selection :: 
    Ptr PrintOperation ->                   
    IO CInt
printOperationGetSupportSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m Bool
    
printOperationGetSupportSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m Bool
printOperationGetSupportSelection a
op = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CInt
result <- Ptr PrintOperation -> IO CInt
gtk_print_operation_get_support_selection Ptr PrintOperation
op'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetSupportSelectionMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetSupportSelectionMethodInfo a signature where
    overloadedMethod = printOperationGetSupportSelection
instance O.OverloadedMethodInfo PrintOperationGetSupportSelectionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationGetSupportSelection",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationGetSupportSelection"
        }
#endif
foreign import ccall "gtk_print_operation_is_finished" gtk_print_operation_is_finished :: 
    Ptr PrintOperation ->                   
    IO CInt
printOperationIsFinished ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m Bool
    
printOperationIsFinished :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m Bool
printOperationIsFinished a
op = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CInt
result <- Ptr PrintOperation -> IO CInt
gtk_print_operation_is_finished Ptr PrintOperation
op'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationIsFinishedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationIsFinishedMethodInfo a signature where
    overloadedMethod = printOperationIsFinished
instance O.OverloadedMethodInfo PrintOperationIsFinishedMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationIsFinished",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationIsFinished"
        }
#endif
foreign import ccall "gtk_print_operation_run" gtk_print_operation_run :: 
    Ptr PrintOperation ->                   
    CUInt ->                                
    Ptr Gtk.Window.Window ->                
    Ptr (Ptr GError) ->                     
    IO CUInt
printOperationRun ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a, Gtk.Window.IsWindow b) =>
    a
    
    -> Gtk.Enums.PrintOperationAction
    
    -> Maybe (b)
    
    -> m Gtk.Enums.PrintOperationResult
    
    
    
    
    
    
    
    
printOperationRun :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintOperation a, IsWindow b) =>
a -> PrintOperationAction -> Maybe b -> m PrintOperationResult
printOperationRun a
op PrintOperationAction
action Maybe b
parent = IO PrintOperationResult -> m PrintOperationResult
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintOperationResult -> m PrintOperationResult)
-> IO PrintOperationResult -> m PrintOperationResult
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let action' :: CUInt
action' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (PrintOperationAction -> Int) -> PrintOperationAction -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PrintOperationAction -> Int
forall a. Enum a => a -> Int
fromEnum) PrintOperationAction
action
    Ptr Window
maybeParent <- case Maybe b
parent of
        Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
forall a. Ptr a
nullPtr
        Just b
jParent -> do
            Ptr Window
jParent' <- b -> IO (Ptr Window)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jParent
            Ptr Window -> IO (Ptr Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jParent'
    IO PrintOperationResult -> IO () -> IO PrintOperationResult
forall a b. IO a -> IO b -> IO a
onException (do
        CUInt
result <- (Ptr (Ptr GError) -> IO CUInt) -> IO CUInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CUInt) -> IO CUInt)
-> (Ptr (Ptr GError) -> IO CUInt) -> IO CUInt
forall a b. (a -> b) -> a -> b
$ Ptr PrintOperation
-> CUInt -> Ptr Window -> Ptr (Ptr GError) -> IO CUInt
gtk_print_operation_run Ptr PrintOperation
op' CUInt
action' Ptr Window
maybeParent
        let result' :: PrintOperationResult
result' = (Int -> PrintOperationResult
forall a. Enum a => Int -> a
toEnum (Int -> PrintOperationResult)
-> (CUInt -> Int) -> CUInt -> PrintOperationResult
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
        Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
parent b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
        PrintOperationResult -> IO PrintOperationResult
forall (m :: * -> *) a. Monad m => a -> m a
return PrintOperationResult
result'
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )
#if defined(ENABLE_OVERLOADING)
data PrintOperationRunMethodInfo
instance (signature ~ (Gtk.Enums.PrintOperationAction -> Maybe (b) -> m Gtk.Enums.PrintOperationResult), MonadIO m, IsPrintOperation a, Gtk.Window.IsWindow b) => O.OverloadedMethod PrintOperationRunMethodInfo a signature where
    overloadedMethod = printOperationRun
instance O.OverloadedMethodInfo PrintOperationRunMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationRun",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationRun"
        }
#endif
foreign import ccall "gtk_print_operation_set_allow_async" gtk_print_operation_set_allow_async :: 
    Ptr PrintOperation ->                   
    CInt ->                                 
    IO ()
printOperationSetAllowAsync ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Bool
    
    -> m ()
printOperationSetAllowAsync :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Bool -> m ()
printOperationSetAllowAsync a
op Bool
allowAsync = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let allowAsync' :: CInt
allowAsync' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
allowAsync
    Ptr PrintOperation -> CInt -> IO ()
gtk_print_operation_set_allow_async Ptr PrintOperation
op' CInt
allowAsync'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetAllowAsyncMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetAllowAsyncMethodInfo a signature where
    overloadedMethod = printOperationSetAllowAsync
instance O.OverloadedMethodInfo PrintOperationSetAllowAsyncMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetAllowAsync",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetAllowAsync"
        }
#endif
foreign import ccall "gtk_print_operation_set_current_page" gtk_print_operation_set_current_page :: 
    Ptr PrintOperation ->                   
    Int32 ->                                
    IO ()
printOperationSetCurrentPage ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Int32
    
    -> m ()
printOperationSetCurrentPage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Int32 -> m ()
printOperationSetCurrentPage a
op Int32
currentPage = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr PrintOperation -> Int32 -> IO ()
gtk_print_operation_set_current_page Ptr PrintOperation
op' Int32
currentPage
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetCurrentPageMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetCurrentPageMethodInfo a signature where
    overloadedMethod = printOperationSetCurrentPage
instance O.OverloadedMethodInfo PrintOperationSetCurrentPageMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetCurrentPage",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetCurrentPage"
        }
#endif
foreign import ccall "gtk_print_operation_set_custom_tab_label" gtk_print_operation_set_custom_tab_label :: 
    Ptr PrintOperation ->                   
    CString ->                              
    IO ()
printOperationSetCustomTabLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Maybe (T.Text)
    
    -> m ()
printOperationSetCustomTabLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Maybe Text -> m ()
printOperationSetCustomTabLabel a
op Maybe Text
label = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
maybeLabel <- case Maybe Text
label of
        Maybe Text
Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just Text
jLabel -> do
            CString
jLabel' <- Text -> IO CString
textToCString Text
jLabel
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jLabel'
    Ptr PrintOperation -> CString -> IO ()
gtk_print_operation_set_custom_tab_label Ptr PrintOperation
op' CString
maybeLabel
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeLabel
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetCustomTabLabelMethodInfo
instance (signature ~ (Maybe (T.Text) -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetCustomTabLabelMethodInfo a signature where
    overloadedMethod = printOperationSetCustomTabLabel
instance O.OverloadedMethodInfo PrintOperationSetCustomTabLabelMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetCustomTabLabel",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetCustomTabLabel"
        }
#endif
foreign import ccall "gtk_print_operation_set_default_page_setup" gtk_print_operation_set_default_page_setup :: 
    Ptr PrintOperation ->                   
    Ptr Gtk.PageSetup.PageSetup ->          
    IO ()
printOperationSetDefaultPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a, Gtk.PageSetup.IsPageSetup b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
printOperationSetDefaultPageSetup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintOperation a, IsPageSetup b) =>
a -> Maybe b -> m ()
printOperationSetDefaultPageSetup a
op Maybe b
defaultPageSetup = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr PageSetup
maybeDefaultPageSetup <- case Maybe b
defaultPageSetup of
        Maybe b
Nothing -> Ptr PageSetup -> IO (Ptr PageSetup)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PageSetup
forall a. Ptr a
nullPtr
        Just b
jDefaultPageSetup -> do
            Ptr PageSetup
jDefaultPageSetup' <- b -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jDefaultPageSetup
            Ptr PageSetup -> IO (Ptr PageSetup)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PageSetup
jDefaultPageSetup'
    Ptr PrintOperation -> Ptr PageSetup -> IO ()
gtk_print_operation_set_default_page_setup Ptr PrintOperation
op' Ptr PageSetup
maybeDefaultPageSetup
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
defaultPageSetup b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetDefaultPageSetupMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsPrintOperation a, Gtk.PageSetup.IsPageSetup b) => O.OverloadedMethod PrintOperationSetDefaultPageSetupMethodInfo a signature where
    overloadedMethod = printOperationSetDefaultPageSetup
instance O.OverloadedMethodInfo PrintOperationSetDefaultPageSetupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetDefaultPageSetup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetDefaultPageSetup"
        }
#endif
foreign import ccall "gtk_print_operation_set_defer_drawing" gtk_print_operation_set_defer_drawing :: 
    Ptr PrintOperation ->                   
    IO ()
printOperationSetDeferDrawing ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> m ()
printOperationSetDeferDrawing :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m ()
printOperationSetDeferDrawing a
op = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr PrintOperation -> IO ()
gtk_print_operation_set_defer_drawing Ptr PrintOperation
op'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetDeferDrawingMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetDeferDrawingMethodInfo a signature where
    overloadedMethod = printOperationSetDeferDrawing
instance O.OverloadedMethodInfo PrintOperationSetDeferDrawingMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetDeferDrawing",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetDeferDrawing"
        }
#endif
foreign import ccall "gtk_print_operation_set_embed_page_setup" gtk_print_operation_set_embed_page_setup :: 
    Ptr PrintOperation ->                   
    CInt ->                                 
    IO ()
printOperationSetEmbedPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Bool
    
    -> m ()
printOperationSetEmbedPageSetup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Bool -> m ()
printOperationSetEmbedPageSetup a
op Bool
embed = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let embed' :: CInt
embed' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
embed
    Ptr PrintOperation -> CInt -> IO ()
gtk_print_operation_set_embed_page_setup Ptr PrintOperation
op' CInt
embed'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetEmbedPageSetupMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetEmbedPageSetupMethodInfo a signature where
    overloadedMethod = printOperationSetEmbedPageSetup
instance O.OverloadedMethodInfo PrintOperationSetEmbedPageSetupMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetEmbedPageSetup",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetEmbedPageSetup"
        }
#endif
foreign import ccall "gtk_print_operation_set_export_filename" gtk_print_operation_set_export_filename :: 
    Ptr PrintOperation ->                   
    CString ->                              
    IO ()
printOperationSetExportFilename ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> [Char]
    
    -> m ()
printOperationSetExportFilename :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> String -> m ()
printOperationSetExportFilename a
op String
filename = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
filename' <- String -> IO CString
stringToCString String
filename
    Ptr PrintOperation -> CString -> IO ()
gtk_print_operation_set_export_filename Ptr PrintOperation
op' CString
filename'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
filename'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetExportFilenameMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetExportFilenameMethodInfo a signature where
    overloadedMethod = printOperationSetExportFilename
instance O.OverloadedMethodInfo PrintOperationSetExportFilenameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetExportFilename",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetExportFilename"
        }
#endif
foreign import ccall "gtk_print_operation_set_has_selection" gtk_print_operation_set_has_selection :: 
    Ptr PrintOperation ->                   
    CInt ->                                 
    IO ()
printOperationSetHasSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Bool
    
    -> m ()
printOperationSetHasSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Bool -> m ()
printOperationSetHasSelection a
op Bool
hasSelection = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let hasSelection' :: CInt
hasSelection' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
hasSelection
    Ptr PrintOperation -> CInt -> IO ()
gtk_print_operation_set_has_selection Ptr PrintOperation
op' CInt
hasSelection'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetHasSelectionMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetHasSelectionMethodInfo a signature where
    overloadedMethod = printOperationSetHasSelection
instance O.OverloadedMethodInfo PrintOperationSetHasSelectionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetHasSelection",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetHasSelection"
        }
#endif
foreign import ccall "gtk_print_operation_set_job_name" gtk_print_operation_set_job_name :: 
    Ptr PrintOperation ->                   
    CString ->                              
    IO ()
printOperationSetJobName ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> T.Text
    
    -> m ()
printOperationSetJobName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Text -> m ()
printOperationSetJobName a
op Text
jobName = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    CString
jobName' <- Text -> IO CString
textToCString Text
jobName
    Ptr PrintOperation -> CString -> IO ()
gtk_print_operation_set_job_name Ptr PrintOperation
op' CString
jobName'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
jobName'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetJobNameMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetJobNameMethodInfo a signature where
    overloadedMethod = printOperationSetJobName
instance O.OverloadedMethodInfo PrintOperationSetJobNameMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetJobName",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetJobName"
        }
#endif
foreign import ccall "gtk_print_operation_set_n_pages" gtk_print_operation_set_n_pages :: 
    Ptr PrintOperation ->                   
    Int32 ->                                
    IO ()
printOperationSetNPages ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Int32
    
    -> m ()
printOperationSetNPages :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Int32 -> m ()
printOperationSetNPages a
op Int32
nPages = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr PrintOperation -> Int32 -> IO ()
gtk_print_operation_set_n_pages Ptr PrintOperation
op' Int32
nPages
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetNPagesMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetNPagesMethodInfo a signature where
    overloadedMethod = printOperationSetNPages
instance O.OverloadedMethodInfo PrintOperationSetNPagesMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetNPages",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetNPages"
        }
#endif
foreign import ccall "gtk_print_operation_set_print_settings" gtk_print_operation_set_print_settings :: 
    Ptr PrintOperation ->                   
    Ptr Gtk.PrintSettings.PrintSettings ->  
    IO ()
printOperationSetPrintSettings ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a, Gtk.PrintSettings.IsPrintSettings b) =>
    a
    
    -> Maybe (b)
    
    -> m ()
printOperationSetPrintSettings :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintOperation a, IsPrintSettings b) =>
a -> Maybe b -> m ()
printOperationSetPrintSettings a
op Maybe b
printSettings = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    Ptr PrintSettings
maybePrintSettings <- case Maybe b
printSettings of
        Maybe b
Nothing -> Ptr PrintSettings -> IO (Ptr PrintSettings)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PrintSettings
forall a. Ptr a
nullPtr
        Just b
jPrintSettings -> do
            Ptr PrintSettings
jPrintSettings' <- b -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
jPrintSettings
            Ptr PrintSettings -> IO (Ptr PrintSettings)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PrintSettings
jPrintSettings'
    Ptr PrintOperation -> Ptr PrintSettings -> IO ()
gtk_print_operation_set_print_settings Ptr PrintOperation
op' Ptr PrintSettings
maybePrintSettings
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    Maybe b -> (b -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe b
printSettings b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetPrintSettingsMethodInfo
instance (signature ~ (Maybe (b) -> m ()), MonadIO m, IsPrintOperation a, Gtk.PrintSettings.IsPrintSettings b) => O.OverloadedMethod PrintOperationSetPrintSettingsMethodInfo a signature where
    overloadedMethod = printOperationSetPrintSettings
instance O.OverloadedMethodInfo PrintOperationSetPrintSettingsMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetPrintSettings",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetPrintSettings"
        }
#endif
foreign import ccall "gtk_print_operation_set_show_progress" gtk_print_operation_set_show_progress :: 
    Ptr PrintOperation ->                   
    CInt ->                                 
    IO ()
printOperationSetShowProgress ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Bool
    
    -> m ()
printOperationSetShowProgress :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Bool -> m ()
printOperationSetShowProgress a
op Bool
showProgress = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let showProgress' :: CInt
showProgress' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
showProgress
    Ptr PrintOperation -> CInt -> IO ()
gtk_print_operation_set_show_progress Ptr PrintOperation
op' CInt
showProgress'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetShowProgressMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetShowProgressMethodInfo a signature where
    overloadedMethod = printOperationSetShowProgress
instance O.OverloadedMethodInfo PrintOperationSetShowProgressMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetShowProgress",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetShowProgress"
        }
#endif
foreign import ccall "gtk_print_operation_set_support_selection" gtk_print_operation_set_support_selection :: 
    Ptr PrintOperation ->                   
    CInt ->                                 
    IO ()
printOperationSetSupportSelection ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Bool
    
    -> m ()
printOperationSetSupportSelection :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Bool -> m ()
printOperationSetSupportSelection a
op Bool
supportSelection = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let supportSelection' :: CInt
supportSelection' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
supportSelection
    Ptr PrintOperation -> CInt -> IO ()
gtk_print_operation_set_support_selection Ptr PrintOperation
op' CInt
supportSelection'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetSupportSelectionMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetSupportSelectionMethodInfo a signature where
    overloadedMethod = printOperationSetSupportSelection
instance O.OverloadedMethodInfo PrintOperationSetSupportSelectionMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetSupportSelection",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetSupportSelection"
        }
#endif
foreign import ccall "gtk_print_operation_set_track_print_status" gtk_print_operation_set_track_print_status :: 
    Ptr PrintOperation ->                   
    CInt ->                                 
    IO ()
printOperationSetTrackPrintStatus ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Bool
    
    -> m ()
printOperationSetTrackPrintStatus :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Bool -> m ()
printOperationSetTrackPrintStatus a
op Bool
trackStatus = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let trackStatus' :: CInt
trackStatus' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
trackStatus
    Ptr PrintOperation -> CInt -> IO ()
gtk_print_operation_set_track_print_status Ptr PrintOperation
op' CInt
trackStatus'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetTrackPrintStatusMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetTrackPrintStatusMethodInfo a signature where
    overloadedMethod = printOperationSetTrackPrintStatus
instance O.OverloadedMethodInfo PrintOperationSetTrackPrintStatusMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetTrackPrintStatus",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetTrackPrintStatus"
        }
#endif
foreign import ccall "gtk_print_operation_set_unit" gtk_print_operation_set_unit :: 
    Ptr PrintOperation ->                   
    CUInt ->                                
    IO ()
printOperationSetUnit ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Gtk.Enums.Unit
    
    -> m ()
printOperationSetUnit :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Unit -> m ()
printOperationSetUnit a
op Unit
unit = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    Ptr PrintOperation -> CUInt -> IO ()
gtk_print_operation_set_unit Ptr PrintOperation
op' CUInt
unit'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetUnitMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetUnitMethodInfo a signature where
    overloadedMethod = printOperationSetUnit
instance O.OverloadedMethodInfo PrintOperationSetUnitMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetUnit",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetUnit"
        }
#endif
foreign import ccall "gtk_print_operation_set_use_full_page" gtk_print_operation_set_use_full_page :: 
    Ptr PrintOperation ->                   
    CInt ->                                 
    IO ()
printOperationSetUseFullPage ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    
    -> Bool
    
    -> m ()
printOperationSetUseFullPage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> Bool -> m ()
printOperationSetUseFullPage a
op Bool
fullPage = 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 PrintOperation
op' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
op
    let fullPage' :: CInt
fullPage' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
fullPage
    Ptr PrintOperation -> CInt -> IO ()
gtk_print_operation_set_use_full_page Ptr PrintOperation
op' CInt
fullPage'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
op
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data PrintOperationSetUseFullPageMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationSetUseFullPageMethodInfo a signature where
    overloadedMethod = printOperationSetUseFullPage
instance O.OverloadedMethodInfo PrintOperationSetUseFullPageMethodInfo a where
    overloadedMethodInfo = O.MethodInfo {
        O.overloadedMethodName = "GI.Gtk.Objects.PrintOperation.printOperationSetUseFullPage",
        O.overloadedMethodURL = "https://hackage.haskell.org/package/gi-gtk-4.0.4/docs/GI-Gtk-Objects-PrintOperation.html#v:printOperationSetUseFullPage"
        }
#endif