{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GtkPrintDialog@ object collects the arguments that
-- are needed to present a print dialog to the user, such
-- as a title for the dialog and whether it should be modal.
-- 
-- The dialog is shown with the 'GI.Gtk.Objects.PrintDialog.printDialogSetup' function.
-- The actual printing can be done with 'GI.Gtk.Objects.PrintDialog.printDialogPrint' or
-- 'GI.Gtk.Objects.PrintDialog.printDialogPrintFile'. These APIs follows the GIO async pattern,
-- and the results can be obtained by calling the corresponding finish methods.
-- 
-- /Since: 4.14/

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

module GI.Gtk.Objects.PrintDialog
    ( 

-- * Exported types
    PrintDialog(..)                         ,
    IsPrintDialog                           ,
    toPrintDialog                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [print]("GI.Gtk.Objects.PrintDialog#g:method:print"), [printFile]("GI.Gtk.Objects.PrintDialog#g:method:printFile"), [printFileFinish]("GI.Gtk.Objects.PrintDialog#g:method:printFileFinish"), [printFinish]("GI.Gtk.Objects.PrintDialog#g:method:printFinish"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [setup]("GI.Gtk.Objects.PrintDialog#g:method:setup"), [setupFinish]("GI.Gtk.Objects.PrintDialog#g:method:setupFinish"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getAcceptLabel]("GI.Gtk.Objects.PrintDialog#g:method:getAcceptLabel"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getModal]("GI.Gtk.Objects.PrintDialog#g:method:getModal"), [getPageSetup]("GI.Gtk.Objects.PrintDialog#g:method:getPageSetup"), [getPrintSettings]("GI.Gtk.Objects.PrintDialog#g:method:getPrintSettings"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getTitle]("GI.Gtk.Objects.PrintDialog#g:method:getTitle").
-- 
-- ==== Setters
-- [setAcceptLabel]("GI.Gtk.Objects.PrintDialog#g:method:setAcceptLabel"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setModal]("GI.Gtk.Objects.PrintDialog#g:method:setModal"), [setPageSetup]("GI.Gtk.Objects.PrintDialog#g:method:setPageSetup"), [setPrintSettings]("GI.Gtk.Objects.PrintDialog#g:method:setPrintSettings"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setTitle]("GI.Gtk.Objects.PrintDialog#g:method:setTitle").

#if defined(ENABLE_OVERLOADING)
    ResolvePrintDialogMethod                ,
#endif

-- ** getAcceptLabel #method:getAcceptLabel#

#if defined(ENABLE_OVERLOADING)
    PrintDialogGetAcceptLabelMethodInfo     ,
#endif
    printDialogGetAcceptLabel               ,


-- ** getModal #method:getModal#

#if defined(ENABLE_OVERLOADING)
    PrintDialogGetModalMethodInfo           ,
#endif
    printDialogGetModal                     ,


-- ** getPageSetup #method:getPageSetup#

#if defined(ENABLE_OVERLOADING)
    PrintDialogGetPageSetupMethodInfo       ,
#endif
    printDialogGetPageSetup                 ,


-- ** getPrintSettings #method:getPrintSettings#

#if defined(ENABLE_OVERLOADING)
    PrintDialogGetPrintSettingsMethodInfo   ,
#endif
    printDialogGetPrintSettings             ,


-- ** getTitle #method:getTitle#

#if defined(ENABLE_OVERLOADING)
    PrintDialogGetTitleMethodInfo           ,
#endif
    printDialogGetTitle                     ,


-- ** new #method:new#

    printDialogNew                          ,


-- ** print #method:print#

#if defined(ENABLE_OVERLOADING)
    PrintDialogPrintMethodInfo              ,
#endif
    printDialogPrint                        ,


-- ** printFile #method:printFile#

#if defined(ENABLE_OVERLOADING)
    PrintDialogPrintFileMethodInfo          ,
#endif
    printDialogPrintFile                    ,


-- ** printFileFinish #method:printFileFinish#

#if defined(ENABLE_OVERLOADING)
    PrintDialogPrintFileFinishMethodInfo    ,
#endif
    printDialogPrintFileFinish              ,


-- ** printFinish #method:printFinish#

#if defined(ENABLE_OVERLOADING)
    PrintDialogPrintFinishMethodInfo        ,
#endif
    printDialogPrintFinish                  ,


-- ** setAcceptLabel #method:setAcceptLabel#

#if defined(ENABLE_OVERLOADING)
    PrintDialogSetAcceptLabelMethodInfo     ,
#endif
    printDialogSetAcceptLabel               ,


-- ** setModal #method:setModal#

#if defined(ENABLE_OVERLOADING)
    PrintDialogSetModalMethodInfo           ,
#endif
    printDialogSetModal                     ,


-- ** setPageSetup #method:setPageSetup#

#if defined(ENABLE_OVERLOADING)
    PrintDialogSetPageSetupMethodInfo       ,
#endif
    printDialogSetPageSetup                 ,


-- ** setPrintSettings #method:setPrintSettings#

#if defined(ENABLE_OVERLOADING)
    PrintDialogSetPrintSettingsMethodInfo   ,
#endif
    printDialogSetPrintSettings             ,


-- ** setTitle #method:setTitle#

#if defined(ENABLE_OVERLOADING)
    PrintDialogSetTitleMethodInfo           ,
#endif
    printDialogSetTitle                     ,


-- ** setup #method:setup#

#if defined(ENABLE_OVERLOADING)
    PrintDialogSetupMethodInfo              ,
#endif
    printDialogSetup                        ,


-- ** setupFinish #method:setupFinish#

#if defined(ENABLE_OVERLOADING)
    PrintDialogSetupFinishMethodInfo        ,
#endif
    printDialogSetupFinish                  ,




 -- * Properties


-- ** acceptLabel #attr:acceptLabel#
-- | A label that may be shown on the accept button of a print dialog
-- that is presented by 'GI.Gtk.Objects.PrintDialog.printDialogSetup'.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    PrintDialogAcceptLabelPropertyInfo      ,
#endif
    constructPrintDialogAcceptLabel         ,
    getPrintDialogAcceptLabel               ,
#if defined(ENABLE_OVERLOADING)
    printDialogAcceptLabel                  ,
#endif
    setPrintDialogAcceptLabel               ,


-- ** modal #attr:modal#
-- | Whether the print dialog is modal.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    PrintDialogModalPropertyInfo            ,
#endif
    constructPrintDialogModal               ,
    getPrintDialogModal                     ,
#if defined(ENABLE_OVERLOADING)
    printDialogModal                        ,
#endif
    setPrintDialogModal                     ,


-- ** pageSetup #attr:pageSetup#
-- | The page setup to use.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    PrintDialogPageSetupPropertyInfo        ,
#endif
    constructPrintDialogPageSetup           ,
    getPrintDialogPageSetup                 ,
#if defined(ENABLE_OVERLOADING)
    printDialogPageSetup                    ,
#endif
    setPrintDialogPageSetup                 ,


-- ** printSettings #attr:printSettings#
-- | The print settings to use.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    PrintDialogPrintSettingsPropertyInfo    ,
#endif
    constructPrintDialogPrintSettings       ,
    getPrintDialogPrintSettings             ,
#if defined(ENABLE_OVERLOADING)
    printDialogPrintSettings                ,
#endif
    setPrintDialogPrintSettings             ,


-- ** title #attr:title#
-- | A title that may be shown on the print dialog that is
-- presented by 'GI.Gtk.Objects.PrintDialog.printDialogSetup'.
-- 
-- /Since: 4.14/

#if defined(ENABLE_OVERLOADING)
    PrintDialogTitlePropertyInfo            ,
#endif
    constructPrintDialogTitle               ,
    getPrintDialogTitle                     ,
#if defined(ENABLE_OVERLOADING)
    printDialogTitle                        ,
#endif
    setPrintDialogTitle                     ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.FontOptions as Cairo.FontOptions
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Flags as Gdk.Flags
import qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import qualified GI.Gdk.Objects.Device as Gdk.Device
import qualified GI.Gdk.Objects.Display as Gdk.Display
import qualified GI.Gdk.Objects.Event as Gdk.Event
import qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import qualified GI.Gdk.Objects.Surface as Gdk.Surface
import qualified GI.Gdk.Objects.Texture as Gdk.Texture
import qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Flags as Gio.Flags
import qualified GI.Gio.Interfaces.ActionGroup as Gio.ActionGroup
import qualified GI.Gio.Interfaces.ActionMap as Gio.ActionMap
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Gio.Objects.Application as Gio.Application
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.Menu as Gio.Menu
import qualified GI.Gio.Objects.MenuModel as Gio.MenuModel
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import qualified GI.Graphene.Structs.Matrix as Graphene.Matrix
import qualified GI.Graphene.Structs.Point as Graphene.Point
import qualified GI.Graphene.Structs.Point3D as Graphene.Point3D
import qualified GI.Graphene.Structs.Rect as Graphene.Rect
import qualified GI.Graphene.Structs.Size as Graphene.Size
import qualified GI.Graphene.Structs.Vec3 as Graphene.Vec3
import qualified GI.Graphene.Structs.Vec4 as Graphene.Vec4
import qualified GI.Gsk.Enums as Gsk.Enums
import qualified GI.Gsk.Objects.GLShader as Gsk.GLShader
import qualified GI.Gsk.Objects.RenderNode as Gsk.RenderNode
import qualified GI.Gsk.Objects.Renderer as Gsk.Renderer
import qualified GI.Gsk.Structs.ColorStop as Gsk.ColorStop
import qualified GI.Gsk.Structs.Path as Gsk.Path
import qualified GI.Gsk.Structs.RoundedRect as Gsk.RoundedRect
import qualified GI.Gsk.Structs.Shadow as Gsk.Shadow
import qualified GI.Gsk.Structs.Stroke as Gsk.Stroke
import qualified GI.Gsk.Structs.Transform as Gsk.Transform
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Native as Gtk.Native
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.Root as Gtk.Root
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.ShortcutManager as Gtk.ShortcutManager
import {-# SOURCE #-} qualified GI.Gtk.Interfaces.StyleProvider as Gtk.StyleProvider
import {-# SOURCE #-} qualified GI.Gtk.Objects.ATContext as Gtk.ATContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Application as Gtk.Application
import {-# SOURCE #-} qualified GI.Gtk.Objects.EventController as Gtk.EventController
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutChild as Gtk.LayoutChild
import {-# SOURCE #-} qualified GI.Gtk.Objects.LayoutManager as Gtk.LayoutManager
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Settings as Gtk.Settings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Snapshot as Gtk.Snapshot
import {-# SOURCE #-} qualified GI.Gtk.Objects.StyleContext as Gtk.StyleContext
import {-# SOURCE #-} qualified GI.Gtk.Objects.Tooltip as Gtk.Tooltip
import {-# SOURCE #-} qualified GI.Gtk.Objects.Widget as Gtk.Widget
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window
import {-# SOURCE #-} qualified GI.Gtk.Objects.WindowGroup as Gtk.WindowGroup
import {-# SOURCE #-} qualified GI.Gtk.Structs.Border as Gtk.Border
import {-# SOURCE #-} qualified GI.Gtk.Structs.PageRange as Gtk.PageRange
import {-# SOURCE #-} qualified GI.Gtk.Structs.PaperSize as Gtk.PaperSize
import {-# SOURCE #-} qualified GI.Gtk.Structs.PrintSetup as Gtk.PrintSetup
import {-# SOURCE #-} qualified GI.Gtk.Structs.Requisition as Gtk.Requisition
import qualified GI.Pango.Enums as Pango.Enums
import qualified GI.Pango.Objects.Context as Pango.Context
import qualified GI.Pango.Objects.FontMap as Pango.FontMap
import qualified GI.Pango.Objects.Layout as Pango.Layout

#else
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings
import {-# SOURCE #-} qualified GI.Gtk.Objects.Window as Gtk.Window
import {-# SOURCE #-} qualified GI.Gtk.Structs.PrintSetup as Gtk.PrintSetup

#endif

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

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

foreign import ccall "gtk_print_dialog_get_type"
    c_gtk_print_dialog_get_type :: IO B.Types.GType

instance B.Types.TypedObject PrintDialog where
    glibType :: IO GType
glibType = IO GType
c_gtk_print_dialog_get_type

instance B.Types.GObject PrintDialog

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolvePrintDialogMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolvePrintDialogMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePrintDialogMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePrintDialogMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePrintDialogMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePrintDialogMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePrintDialogMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePrintDialogMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePrintDialogMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePrintDialogMethod "print" o = PrintDialogPrintMethodInfo
    ResolvePrintDialogMethod "printFile" o = PrintDialogPrintFileMethodInfo
    ResolvePrintDialogMethod "printFileFinish" o = PrintDialogPrintFileFinishMethodInfo
    ResolvePrintDialogMethod "printFinish" o = PrintDialogPrintFinishMethodInfo
    ResolvePrintDialogMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePrintDialogMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePrintDialogMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePrintDialogMethod "setup" o = PrintDialogSetupMethodInfo
    ResolvePrintDialogMethod "setupFinish" o = PrintDialogSetupFinishMethodInfo
    ResolvePrintDialogMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePrintDialogMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePrintDialogMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePrintDialogMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePrintDialogMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePrintDialogMethod "getAcceptLabel" o = PrintDialogGetAcceptLabelMethodInfo
    ResolvePrintDialogMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePrintDialogMethod "getModal" o = PrintDialogGetModalMethodInfo
    ResolvePrintDialogMethod "getPageSetup" o = PrintDialogGetPageSetupMethodInfo
    ResolvePrintDialogMethod "getPrintSettings" o = PrintDialogGetPrintSettingsMethodInfo
    ResolvePrintDialogMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePrintDialogMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePrintDialogMethod "getTitle" o = PrintDialogGetTitleMethodInfo
    ResolvePrintDialogMethod "setAcceptLabel" o = PrintDialogSetAcceptLabelMethodInfo
    ResolvePrintDialogMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePrintDialogMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePrintDialogMethod "setModal" o = PrintDialogSetModalMethodInfo
    ResolvePrintDialogMethod "setPageSetup" o = PrintDialogSetPageSetupMethodInfo
    ResolvePrintDialogMethod "setPrintSettings" o = PrintDialogSetPrintSettingsMethodInfo
    ResolvePrintDialogMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePrintDialogMethod "setTitle" o = PrintDialogSetTitleMethodInfo
    ResolvePrintDialogMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- VVV Prop "accept-label"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@accept-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' printDialog #acceptLabel
-- @
getPrintDialogAcceptLabel :: (MonadIO m, IsPrintDialog o) => o -> m T.Text
getPrintDialogAcceptLabel :: forall (m :: * -> *) o. (MonadIO m, IsPrintDialog o) => o -> m Text
getPrintDialogAcceptLabel o
obj = IO Text -> m Text
forall a. IO a -> m a
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
"getPrintDialogAcceptLabel" (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
"accept-label"

-- | Set the value of the “@accept-label@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' printDialog [ #acceptLabel 'Data.GI.Base.Attributes.:=' value ]
-- @
setPrintDialogAcceptLabel :: (MonadIO m, IsPrintDialog o) => o -> T.Text -> m ()
setPrintDialogAcceptLabel :: forall (m :: * -> *) o.
(MonadIO m, IsPrintDialog o) =>
o -> Text -> m ()
setPrintDialogAcceptLabel o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
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
"accept-label" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@accept-label@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPrintDialogAcceptLabel :: (IsPrintDialog o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPrintDialogAcceptLabel :: forall o (m :: * -> *).
(IsPrintDialog o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPrintDialogAcceptLabel Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"accept-label" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data PrintDialogAcceptLabelPropertyInfo
instance AttrInfo PrintDialogAcceptLabelPropertyInfo where
    type AttrAllowedOps PrintDialogAcceptLabelPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintDialogAcceptLabelPropertyInfo = IsPrintDialog
    type AttrSetTypeConstraint PrintDialogAcceptLabelPropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PrintDialogAcceptLabelPropertyInfo = (~) T.Text
    type AttrTransferType PrintDialogAcceptLabelPropertyInfo = T.Text
    type AttrGetType PrintDialogAcceptLabelPropertyInfo = T.Text
    type AttrLabel PrintDialogAcceptLabelPropertyInfo = "accept-label"
    type AttrOrigin PrintDialogAcceptLabelPropertyInfo = PrintDialog
    attrGet = getPrintDialogAcceptLabel
    attrSet = setPrintDialogAcceptLabel
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintDialogAcceptLabel
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.acceptLabel"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#g:attr:acceptLabel"
        })
#endif

-- VVV Prop "modal"
   -- Type: TBasicType TBoolean
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@modal@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' printDialog #modal
-- @
getPrintDialogModal :: (MonadIO m, IsPrintDialog o) => o -> m Bool
getPrintDialogModal :: forall (m :: * -> *) o. (MonadIO m, IsPrintDialog o) => o -> m Bool
getPrintDialogModal o
obj = IO Bool -> m Bool
forall a. IO a -> m a
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
"modal"

-- | Set the value of the “@modal@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' printDialog [ #modal 'Data.GI.Base.Attributes.:=' value ]
-- @
setPrintDialogModal :: (MonadIO m, IsPrintDialog o) => o -> Bool -> m ()
setPrintDialogModal :: forall (m :: * -> *) o.
(MonadIO m, IsPrintDialog o) =>
o -> Bool -> m ()
setPrintDialogModal o
obj Bool
val = IO () -> m ()
forall a. IO a -> m a
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
"modal" Bool
val

-- | Construct a `GValueConstruct` with valid value for the “@modal@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPrintDialogModal :: (IsPrintDialog o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrintDialogModal :: forall o (m :: * -> *).
(IsPrintDialog o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrintDialogModal Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"modal" Bool
val

#if defined(ENABLE_OVERLOADING)
data PrintDialogModalPropertyInfo
instance AttrInfo PrintDialogModalPropertyInfo where
    type AttrAllowedOps PrintDialogModalPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintDialogModalPropertyInfo = IsPrintDialog
    type AttrSetTypeConstraint PrintDialogModalPropertyInfo = (~) Bool
    type AttrTransferTypeConstraint PrintDialogModalPropertyInfo = (~) Bool
    type AttrTransferType PrintDialogModalPropertyInfo = Bool
    type AttrGetType PrintDialogModalPropertyInfo = Bool
    type AttrLabel PrintDialogModalPropertyInfo = "modal"
    type AttrOrigin PrintDialogModalPropertyInfo = PrintDialog
    attrGet = getPrintDialogModal
    attrSet = setPrintDialogModal
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintDialogModal
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.modal"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#g:attr:modal"
        })
#endif

-- VVV Prop "page-setup"
   -- Type: TInterface (Name {namespace = "Gtk", name = "PageSetup"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@page-setup@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' printDialog #pageSetup
-- @
getPrintDialogPageSetup :: (MonadIO m, IsPrintDialog o) => o -> m Gtk.PageSetup.PageSetup
getPrintDialogPageSetup :: forall (m :: * -> *) o.
(MonadIO m, IsPrintDialog o) =>
o -> m PageSetup
getPrintDialogPageSetup o
obj = IO PageSetup -> m PageSetup
forall a. IO a -> m a
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
"getPrintDialogPageSetup" (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
"page-setup" ManagedPtr PageSetup -> PageSetup
Gtk.PageSetup.PageSetup

-- | Set the value of the “@page-setup@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' printDialog [ #pageSetup 'Data.GI.Base.Attributes.:=' value ]
-- @
setPrintDialogPageSetup :: (MonadIO m, IsPrintDialog o, Gtk.PageSetup.IsPageSetup a) => o -> a -> m ()
setPrintDialogPageSetup :: forall (m :: * -> *) o a.
(MonadIO m, IsPrintDialog o, IsPageSetup a) =>
o -> a -> m ()
setPrintDialogPageSetup o
obj a
val = IO () -> m ()
forall a. IO a -> m a
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
"page-setup" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)

-- | Construct a `GValueConstruct` with valid value for the “@page-setup@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPrintDialogPageSetup :: (IsPrintDialog o, MIO.MonadIO m, Gtk.PageSetup.IsPageSetup a) => a -> m (GValueConstruct o)
constructPrintDialogPageSetup :: forall o (m :: * -> *) a.
(IsPrintDialog o, MonadIO m, IsPageSetup a) =>
a -> m (GValueConstruct o)
constructPrintDialogPageSetup a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"page-setup" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data PrintDialogPageSetupPropertyInfo
instance AttrInfo PrintDialogPageSetupPropertyInfo where
    type AttrAllowedOps PrintDialogPageSetupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintDialogPageSetupPropertyInfo = IsPrintDialog
    type AttrSetTypeConstraint PrintDialogPageSetupPropertyInfo = Gtk.PageSetup.IsPageSetup
    type AttrTransferTypeConstraint PrintDialogPageSetupPropertyInfo = Gtk.PageSetup.IsPageSetup
    type AttrTransferType PrintDialogPageSetupPropertyInfo = Gtk.PageSetup.PageSetup
    type AttrGetType PrintDialogPageSetupPropertyInfo = Gtk.PageSetup.PageSetup
    type AttrLabel PrintDialogPageSetupPropertyInfo = "page-setup"
    type AttrOrigin PrintDialogPageSetupPropertyInfo = PrintDialog
    attrGet = getPrintDialogPageSetup
    attrSet = setPrintDialogPageSetup
    attrTransfer _ v = do
        unsafeCastTo Gtk.PageSetup.PageSetup v
    attrConstruct = constructPrintDialogPageSetup
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.pageSetup"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#g:attr:pageSetup"
        })
#endif

-- VVV Prop "print-settings"
   -- Type: TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@print-settings@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' printDialog #printSettings
-- @
getPrintDialogPrintSettings :: (MonadIO m, IsPrintDialog o) => o -> m Gtk.PrintSettings.PrintSettings
getPrintDialogPrintSettings :: forall (m :: * -> *) o.
(MonadIO m, IsPrintDialog o) =>
o -> m PrintSettings
getPrintDialogPrintSettings o
obj = IO PrintSettings -> m PrintSettings
forall a. IO a -> m a
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
"getPrintDialogPrintSettings" (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

-- | Set the value of the “@print-settings@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' printDialog [ #printSettings 'Data.GI.Base.Attributes.:=' value ]
-- @
setPrintDialogPrintSettings :: (MonadIO m, IsPrintDialog o, Gtk.PrintSettings.IsPrintSettings a) => o -> a -> m ()
setPrintDialogPrintSettings :: forall (m :: * -> *) o a.
(MonadIO m, IsPrintDialog o, IsPrintSettings a) =>
o -> a -> m ()
setPrintDialogPrintSettings o
obj a
val = IO () -> m ()
forall a. IO a -> m a
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)

-- | Construct a `GValueConstruct` with valid value for the “@print-settings@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPrintDialogPrintSettings :: (IsPrintDialog o, MIO.MonadIO m, Gtk.PrintSettings.IsPrintSettings a) => a -> m (GValueConstruct o)
constructPrintDialogPrintSettings :: forall o (m :: * -> *) a.
(IsPrintDialog o, MonadIO m, IsPrintSettings a) =>
a -> m (GValueConstruct o)
constructPrintDialogPrintSettings a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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)

#if defined(ENABLE_OVERLOADING)
data PrintDialogPrintSettingsPropertyInfo
instance AttrInfo PrintDialogPrintSettingsPropertyInfo where
    type AttrAllowedOps PrintDialogPrintSettingsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintDialogPrintSettingsPropertyInfo = IsPrintDialog
    type AttrSetTypeConstraint PrintDialogPrintSettingsPropertyInfo = Gtk.PrintSettings.IsPrintSettings
    type AttrTransferTypeConstraint PrintDialogPrintSettingsPropertyInfo = Gtk.PrintSettings.IsPrintSettings
    type AttrTransferType PrintDialogPrintSettingsPropertyInfo = Gtk.PrintSettings.PrintSettings
    type AttrGetType PrintDialogPrintSettingsPropertyInfo = Gtk.PrintSettings.PrintSettings
    type AttrLabel PrintDialogPrintSettingsPropertyInfo = "print-settings"
    type AttrOrigin PrintDialogPrintSettingsPropertyInfo = PrintDialog
    attrGet = getPrintDialogPrintSettings
    attrSet = setPrintDialogPrintSettings
    attrTransfer _ v = do
        unsafeCastTo Gtk.PrintSettings.PrintSettings v
    attrConstruct = constructPrintDialogPrintSettings
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printSettings"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#g:attr:printSettings"
        })
#endif

-- VVV Prop "title"
   -- Type: TBasicType TUTF8
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@title@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' printDialog #title
-- @
getPrintDialogTitle :: (MonadIO m, IsPrintDialog o) => o -> m T.Text
getPrintDialogTitle :: forall (m :: * -> *) o. (MonadIO m, IsPrintDialog o) => o -> m Text
getPrintDialogTitle o
obj = IO Text -> m Text
forall a. IO a -> m a
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
"getPrintDialogTitle" (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
"title"

-- | Set the value of the “@title@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' printDialog [ #title 'Data.GI.Base.Attributes.:=' value ]
-- @
setPrintDialogTitle :: (MonadIO m, IsPrintDialog o) => o -> T.Text -> m ()
setPrintDialogTitle :: forall (m :: * -> *) o.
(MonadIO m, IsPrintDialog o) =>
o -> Text -> m ()
setPrintDialogTitle o
obj Text
val = IO () -> m ()
forall a. IO a -> m a
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
"title" (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val)

-- | Construct a `GValueConstruct` with valid value for the “@title@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructPrintDialogTitle :: (IsPrintDialog o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPrintDialogTitle :: forall o (m :: * -> *).
(IsPrintDialog o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPrintDialogTitle Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
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 a. IO a -> IO a
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
"title" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)

#if defined(ENABLE_OVERLOADING)
data PrintDialogTitlePropertyInfo
instance AttrInfo PrintDialogTitlePropertyInfo where
    type AttrAllowedOps PrintDialogTitlePropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintDialogTitlePropertyInfo = IsPrintDialog
    type AttrSetTypeConstraint PrintDialogTitlePropertyInfo = (~) T.Text
    type AttrTransferTypeConstraint PrintDialogTitlePropertyInfo = (~) T.Text
    type AttrTransferType PrintDialogTitlePropertyInfo = T.Text
    type AttrGetType PrintDialogTitlePropertyInfo = T.Text
    type AttrLabel PrintDialogTitlePropertyInfo = "title"
    type AttrOrigin PrintDialogTitlePropertyInfo = PrintDialog
    attrGet = getPrintDialogTitle
    attrSet = setPrintDialogTitle
    attrTransfer _ v = do
        return v
    attrConstruct = constructPrintDialogTitle
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.title"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#g:attr:title"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PrintDialog
type instance O.AttributeList PrintDialog = PrintDialogAttributeList
type PrintDialogAttributeList = ('[ '("acceptLabel", PrintDialogAcceptLabelPropertyInfo), '("modal", PrintDialogModalPropertyInfo), '("pageSetup", PrintDialogPageSetupPropertyInfo), '("printSettings", PrintDialogPrintSettingsPropertyInfo), '("title", PrintDialogTitlePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
printDialogAcceptLabel :: AttrLabelProxy "acceptLabel"
printDialogAcceptLabel = AttrLabelProxy

printDialogModal :: AttrLabelProxy "modal"
printDialogModal = AttrLabelProxy

printDialogPageSetup :: AttrLabelProxy "pageSetup"
printDialogPageSetup = AttrLabelProxy

printDialogPrintSettings :: AttrLabelProxy "printSettings"
printDialogPrintSettings = AttrLabelProxy

printDialogTitle :: AttrLabelProxy "title"
printDialogTitle = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PrintDialog = PrintDialogSignalList
type PrintDialogSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

-- method PrintDialog::new
-- method type : Constructor
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "PrintDialog" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_new" gtk_print_dialog_new :: 
    IO (Ptr PrintDialog)

-- | Creates a new @GtkPrintDialog@ object.
-- 
-- /Since: 4.14/
printDialogNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m PrintDialog
    -- ^ __Returns:__ the new @GtkPrintDialog@
printDialogNew :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m PrintDialog
printDialogNew  = IO PrintDialog -> m PrintDialog
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintDialog -> m PrintDialog)
-> IO PrintDialog -> m PrintDialog
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
result <- IO (Ptr PrintDialog)
gtk_print_dialog_new
    Text -> Ptr PrintDialog -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printDialogNew" Ptr PrintDialog
result
    PrintDialog
result' <- ((ManagedPtr PrintDialog -> PrintDialog)
-> Ptr PrintDialog -> IO PrintDialog
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PrintDialog -> PrintDialog
PrintDialog) Ptr PrintDialog
result
    PrintDialog -> IO PrintDialog
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PrintDialog
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PrintDialog::get_accept_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_get_accept_label" gtk_print_dialog_get_accept_label :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    IO CString

-- | Returns the label that will be shown on the
-- accept button of the print dialog.
-- 
-- /Since: 4.14/
printDialogGetAcceptLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> m T.Text
    -- ^ __Returns:__ the accept label
printDialogGetAcceptLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintDialog a) =>
a -> m Text
printDialogGetAcceptLabel a
self = IO Text -> m Text
forall a. IO a -> m a
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 PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr PrintDialog -> IO CString
gtk_print_dialog_get_accept_label Ptr PrintDialog
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printDialogGetAcceptLabel" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PrintDialogGetAcceptLabelMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrintDialog a) => O.OverloadedMethod PrintDialogGetAcceptLabelMethodInfo a signature where
    overloadedMethod = printDialogGetAcceptLabel

instance O.OverloadedMethodInfo PrintDialogGetAcceptLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogGetAcceptLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogGetAcceptLabel"
        })


#endif

-- method PrintDialog::get_modal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_get_modal" gtk_print_dialog_get_modal :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    IO CInt

-- | Returns whether the print dialog blocks
-- interaction with the parent window while
-- it is presented.
-- 
-- /Since: 4.14/
printDialogGetModal ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> m Bool
    -- ^ __Returns:__ whether the print dialog is modal
printDialogGetModal :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintDialog a) =>
a -> m Bool
printDialogGetModal a
self = IO Bool -> m Bool
forall a. IO a -> m a
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 PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CInt
result <- Ptr PrintDialog -> IO CInt
gtk_print_dialog_get_modal Ptr PrintDialog
self'
    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
self
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PrintDialogGetModalMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrintDialog a) => O.OverloadedMethod PrintDialogGetModalMethodInfo a signature where
    overloadedMethod = printDialogGetModal

instance O.OverloadedMethodInfo PrintDialogGetModalMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogGetModal",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogGetModal"
        })


#endif

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

foreign import ccall "gtk_print_dialog_get_page_setup" gtk_print_dialog_get_page_setup :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    IO (Ptr Gtk.PageSetup.PageSetup)

-- | Returns the page setup.
-- 
-- /Since: 4.14/
printDialogGetPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> m Gtk.PageSetup.PageSetup
    -- ^ __Returns:__ the page setup
printDialogGetPageSetup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintDialog a) =>
a -> m PageSetup
printDialogGetPageSetup a
self = IO PageSetup -> m PageSetup
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PageSetup -> m PageSetup) -> IO PageSetup -> m PageSetup
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr PageSetup
result <- Ptr PrintDialog -> IO (Ptr PageSetup)
gtk_print_dialog_get_page_setup Ptr PrintDialog
self'
    Text -> Ptr PageSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printDialogGetPageSetup" 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
self
    PageSetup -> IO PageSetup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result'

#if defined(ENABLE_OVERLOADING)
data PrintDialogGetPageSetupMethodInfo
instance (signature ~ (m Gtk.PageSetup.PageSetup), MonadIO m, IsPrintDialog a) => O.OverloadedMethod PrintDialogGetPageSetupMethodInfo a signature where
    overloadedMethod = printDialogGetPageSetup

instance O.OverloadedMethodInfo PrintDialogGetPageSetupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogGetPageSetup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogGetPageSetup"
        })


#endif

-- method PrintDialog::get_print_settings
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "PrintSettings" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_get_print_settings" gtk_print_dialog_get_print_settings :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    IO (Ptr Gtk.PrintSettings.PrintSettings)

-- | Returns the print settings for the print dialog.
-- 
-- /Since: 4.14/
printDialogGetPrintSettings ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> m Gtk.PrintSettings.PrintSettings
    -- ^ __Returns:__ the settings
printDialogGetPrintSettings :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintDialog a) =>
a -> m PrintSettings
printDialogGetPrintSettings a
self = IO PrintSettings -> m PrintSettings
forall a. IO a -> m a
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 PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr PrintSettings
result <- Ptr PrintDialog -> IO (Ptr PrintSettings)
gtk_print_dialog_get_print_settings Ptr PrintDialog
self'
    Text -> Ptr PrintSettings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printDialogGetPrintSettings" 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
self
    PrintSettings -> IO PrintSettings
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result'

#if defined(ENABLE_OVERLOADING)
data PrintDialogGetPrintSettingsMethodInfo
instance (signature ~ (m Gtk.PrintSettings.PrintSettings), MonadIO m, IsPrintDialog a) => O.OverloadedMethod PrintDialogGetPrintSettingsMethodInfo a signature where
    overloadedMethod = printDialogGetPrintSettings

instance O.OverloadedMethodInfo PrintDialogGetPrintSettingsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogGetPrintSettings",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogGetPrintSettings"
        })


#endif

-- method PrintDialog::get_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TUTF8)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_get_title" gtk_print_dialog_get_title :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    IO CString

-- | Returns the title that will be shown on the
-- print dialog.
-- 
-- /Since: 4.14/
printDialogGetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> m T.Text
    -- ^ __Returns:__ the title
printDialogGetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintDialog a) =>
a -> m Text
printDialogGetTitle a
self = IO Text -> m Text
forall a. IO a -> m a
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 PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
result <- Ptr PrintDialog -> IO CString
gtk_print_dialog_get_title Ptr PrintDialog
self'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printDialogGetTitle" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    Text -> IO Text
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PrintDialogGetTitleMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrintDialog a) => O.OverloadedMethod PrintDialogGetTitleMethodInfo a signature where
    overloadedMethod = printDialogGetTitle

instance O.OverloadedMethodInfo PrintDialogGetTitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogGetTitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogGetTitle"
        })


#endif

-- method PrintDialog::print
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent `GtkWindow`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSetup" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkPrintSetup` to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GCancellable` to cancel the operation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a callback to call when the operation is complete"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 5
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_print" gtk_print_dialog_print :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    Ptr Gtk.Window.Window ->                -- parent : TInterface (Name {namespace = "Gtk", name = "Window"})
    Ptr Gtk.PrintSetup.PrintSetup ->        -- setup : TInterface (Name {namespace = "Gtk", name = "PrintSetup"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | This function prints content from a stream.
-- 
-- If you pass @NULL@ as /@setup@/, then this method will present a print dialog.
-- Otherwise, it will attempt to print directly, without user interaction.
-- 
-- The /@callback@/ will be called when the printing is done. It should call
-- 'GI.Gtk.Objects.PrintDialog.printDialogPrintFinish' to obtain the results.
-- 
-- /Since: 4.14/
printDialogPrint ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> Maybe (b)
    -- ^ /@parent@/: the parent @GtkWindow@
    -> Maybe (Gtk.PrintSetup.PrintSetup)
    -- ^ /@setup@/: the @GtkPrintSetup@ to use
    -> Maybe (c)
    -- ^ /@cancellable@/: a @GCancellable@ to cancel the operation
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a callback to call when the operation is complete
    -> m ()
printDialogPrint :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsPrintDialog a, IsWindow b,
 IsCancellable c) =>
a
-> Maybe b
-> Maybe PrintSetup
-> Maybe c
-> Maybe AsyncReadyCallback
-> m ()
printDialogPrint a
self Maybe b
parent Maybe PrintSetup
setup Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Window
maybeParent <- case Maybe b
parent of
        Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jParent'
    Ptr PrintSetup
maybeSetup <- case Maybe PrintSetup
setup of
        Maybe PrintSetup
Nothing -> Ptr PrintSetup -> IO (Ptr PrintSetup)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PrintSetup
forall a. Ptr a
nullPtr
        Just PrintSetup
jSetup -> do
            Ptr PrintSetup
jSetup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
jSetup
            Ptr PrintSetup -> IO (Ptr PrintSetup)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PrintSetup
jSetup'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr PrintDialog
-> Ptr Window
-> Ptr PrintSetup
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gtk_print_dialog_print Ptr PrintDialog
self' Ptr Window
maybeParent Ptr PrintSetup
maybeSetup Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    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
    Maybe PrintSetup -> (PrintSetup -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe PrintSetup
setup PrintSetup -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintDialogPrintMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gtk.PrintSetup.PrintSetup) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsPrintDialog a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod PrintDialogPrintMethodInfo a signature where
    overloadedMethod = printDialogPrint

instance O.OverloadedMethodInfo PrintDialogPrintMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogPrint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogPrint"
        })


#endif

-- method PrintDialog::print_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent `GtkWindow`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSetup" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GtkPrintSetup` to use"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file"
--           , argType = TInterface Name { namespace = "Gio" , name = "File" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GFile` to print"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GCancellable` to cancel the operation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a callback to call when the operation is complete"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 6
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_print_file" gtk_print_dialog_print_file :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    Ptr Gtk.Window.Window ->                -- parent : TInterface (Name {namespace = "Gtk", name = "Window"})
    Ptr Gtk.PrintSetup.PrintSetup ->        -- setup : TInterface (Name {namespace = "Gtk", name = "PrintSetup"})
    Ptr Gio.File.File ->                    -- file : TInterface (Name {namespace = "Gio", name = "File"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | This function prints a file.
-- 
-- If you pass @NULL@ as /@setup@/, then this method will present a print dialog.
-- Otherwise, it will attempt to print directly, without user interaction.
-- 
-- The /@callback@/ will be called when the printing is done. It should call
-- 'GI.Gtk.Objects.PrintDialog.printDialogPrintFileFinish' to obtain the results.
-- 
-- /Since: 4.14/
printDialogPrintFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a, Gtk.Window.IsWindow b, Gio.File.IsFile c, Gio.Cancellable.IsCancellable d) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> Maybe (b)
    -- ^ /@parent@/: the parent @GtkWindow@
    -> Maybe (Gtk.PrintSetup.PrintSetup)
    -- ^ /@setup@/: the @GtkPrintSetup@ to use
    -> c
    -- ^ /@file@/: the @GFile@ to print
    -> Maybe (d)
    -- ^ /@cancellable@/: a @GCancellable@ to cancel the operation
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a callback to call when the operation is complete
    -> m ()
printDialogPrintFile :: forall (m :: * -> *) a b c d.
(HasCallStack, MonadIO m, IsPrintDialog a, IsWindow b, IsFile c,
 IsCancellable d) =>
a
-> Maybe b
-> Maybe PrintSetup
-> c
-> Maybe d
-> Maybe AsyncReadyCallback
-> m ()
printDialogPrintFile a
self Maybe b
parent Maybe PrintSetup
setup c
file Maybe d
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Window
maybeParent <- case Maybe b
parent of
        Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jParent'
    Ptr PrintSetup
maybeSetup <- case Maybe PrintSetup
setup of
        Maybe PrintSetup
Nothing -> Ptr PrintSetup -> IO (Ptr PrintSetup)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PrintSetup
forall a. Ptr a
nullPtr
        Just PrintSetup
jSetup -> do
            Ptr PrintSetup
jSetup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
jSetup
            Ptr PrintSetup -> IO (Ptr PrintSetup)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PrintSetup
jSetup'
    Ptr File
file' <- c -> IO (Ptr File)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
file
    Ptr Cancellable
maybeCancellable <- case Maybe d
cancellable of
        Maybe d
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just d
jCancellable -> do
            Ptr Cancellable
jCancellable' <- d -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr d
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr PrintDialog
-> Ptr Window
-> Ptr PrintSetup
-> Ptr File
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gtk_print_dialog_print_file Ptr PrintDialog
self' Ptr Window
maybeParent Ptr PrintSetup
maybeSetup Ptr File
file' Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    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
    Maybe PrintSetup -> (PrintSetup -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe PrintSetup
setup PrintSetup -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr c
file
    Maybe d -> (d -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe d
cancellable d -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintDialogPrintFileMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (Gtk.PrintSetup.PrintSetup) -> c -> Maybe (d) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsPrintDialog a, Gtk.Window.IsWindow b, Gio.File.IsFile c, Gio.Cancellable.IsCancellable d) => O.OverloadedMethod PrintDialogPrintFileMethodInfo a signature where
    overloadedMethod = printDialogPrintFile

instance O.OverloadedMethodInfo PrintDialogPrintFileMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogPrintFile",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogPrintFile"
        })


#endif

-- method PrintDialog::print_file_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GAsyncResult`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gtk_print_dialog_print_file_finish" gtk_print_dialog_print_file_finish :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Finishes the 'GI.Gtk.Objects.PrintDialog.printDialogPrintFile' call and
-- returns the results.
-- 
-- /Since: 4.14/
printDialogPrintFileFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> b
    -- ^ /@result@/: a @GAsyncResult@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
printDialogPrintFileFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintDialog a, IsAsyncResult b) =>
a -> b -> m ()
printDialogPrintFileFinish a
self b
result_ = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr PrintDialog -> Ptr AsyncResult -> Ptr (Ptr GError) -> IO CInt
gtk_print_dialog_print_file_finish Ptr PrintDialog
self' Ptr AsyncResult
result_'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data PrintDialogPrintFileFinishMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPrintDialog a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod PrintDialogPrintFileFinishMethodInfo a signature where
    overloadedMethod = printDialogPrintFileFinish

instance O.OverloadedMethodInfo PrintDialogPrintFileFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogPrintFileFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogPrintFileFinish"
        })


#endif

-- method PrintDialog::print_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GAsyncResult`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gio" , name = "OutputStream" })
-- throws : True
-- Skip return : False

foreign import ccall "gtk_print_dialog_print_finish" gtk_print_dialog_print_finish :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gio.OutputStream.OutputStream)

-- | Finishes the 'GI.Gtk.Objects.PrintDialog.printDialogPrint' call and
-- returns the results.
-- 
-- If the call was successful, the content to be printed should be
-- written to the returned output stream. Otherwise, @NULL@ is returned.
-- 
-- The overall results of the print operation will be returned in the
-- 'GI.Gio.Objects.OutputStream.outputStreamClose' call, so if you are interested in the
-- results, you need to explicitly close the output stream (it will be
-- closed automatically if you just unref it). Be aware that the close
-- call may not be instant as it operation will for the printer to finish
-- printing.
-- 
-- /Since: 4.14/
printDialogPrintFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> b
    -- ^ /@result@/: a @GAsyncResult@
    -> m (Maybe Gio.OutputStream.OutputStream)
    -- ^ __Returns:__ a t'GI.Gio.Objects.OutputStream.OutputStream' /(Can throw 'Data.GI.Base.GError.GError')/
printDialogPrintFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintDialog a, IsAsyncResult b) =>
a -> b -> m (Maybe OutputStream)
printDialogPrintFinish a
self b
result_ = IO (Maybe OutputStream) -> m (Maybe OutputStream)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe OutputStream) -> m (Maybe OutputStream))
-> IO (Maybe OutputStream) -> m (Maybe OutputStream)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO (Maybe OutputStream) -> IO () -> IO (Maybe OutputStream)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr OutputStream
result <- (Ptr (Ptr GError) -> IO (Ptr OutputStream))
-> IO (Ptr OutputStream)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr OutputStream))
 -> IO (Ptr OutputStream))
-> (Ptr (Ptr GError) -> IO (Ptr OutputStream))
-> IO (Ptr OutputStream)
forall a b. (a -> b) -> a -> b
$ Ptr PrintDialog
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr OutputStream)
gtk_print_dialog_print_finish Ptr PrintDialog
self' Ptr AsyncResult
result_'
        Maybe OutputStream
maybeResult <- Ptr OutputStream
-> (Ptr OutputStream -> IO OutputStream) -> IO (Maybe OutputStream)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr OutputStream
result ((Ptr OutputStream -> IO OutputStream) -> IO (Maybe OutputStream))
-> (Ptr OutputStream -> IO OutputStream) -> IO (Maybe OutputStream)
forall a b. (a -> b) -> a -> b
$ \Ptr OutputStream
result' -> do
            OutputStream
result'' <- ((ManagedPtr OutputStream -> OutputStream)
-> Ptr OutputStream -> IO OutputStream
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr OutputStream -> OutputStream
Gio.OutputStream.OutputStream) Ptr OutputStream
result'
            OutputStream -> IO OutputStream
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return OutputStream
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        Maybe OutputStream -> IO (Maybe OutputStream)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe OutputStream
maybeResult
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data PrintDialogPrintFinishMethodInfo
instance (signature ~ (b -> m (Maybe Gio.OutputStream.OutputStream)), MonadIO m, IsPrintDialog a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod PrintDialogPrintFinishMethodInfo a signature where
    overloadedMethod = printDialogPrintFinish

instance O.OverloadedMethodInfo PrintDialogPrintFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogPrintFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogPrintFinish"
        })


#endif

-- method PrintDialog::set_accept_label
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "accept_label"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new accept label"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_set_accept_label" gtk_print_dialog_set_accept_label :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    CString ->                              -- accept_label : TBasicType TUTF8
    IO ()

-- | Sets the label that will be shown on the
-- accept button of the print dialog shown for
-- 'GI.Gtk.Objects.PrintDialog.printDialogSetup'.
-- 
-- /Since: 4.14/
printDialogSetAcceptLabel ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> T.Text
    -- ^ /@acceptLabel@/: the new accept label
    -> m ()
printDialogSetAcceptLabel :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintDialog a) =>
a -> Text -> m ()
printDialogSetAcceptLabel a
self Text
acceptLabel = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
acceptLabel' <- Text -> IO CString
textToCString Text
acceptLabel
    Ptr PrintDialog -> CString -> IO ()
gtk_print_dialog_set_accept_label Ptr PrintDialog
self' CString
acceptLabel'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
acceptLabel'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintDialogSetAcceptLabelMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintDialog a) => O.OverloadedMethod PrintDialogSetAcceptLabelMethodInfo a signature where
    overloadedMethod = printDialogSetAcceptLabel

instance O.OverloadedMethodInfo PrintDialogSetAcceptLabelMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogSetAcceptLabel",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogSetAcceptLabel"
        })


#endif

-- method PrintDialog::set_modal
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "modal"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_set_modal" gtk_print_dialog_set_modal :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    CInt ->                                 -- modal : TBasicType TBoolean
    IO ()

-- | Sets whether the print dialog blocks
-- interaction with the parent window while
-- it is presented.
-- 
-- /Since: 4.14/
printDialogSetModal ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> Bool
    -- ^ /@modal@/: the new value
    -> m ()
printDialogSetModal :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintDialog a) =>
a -> Bool -> m ()
printDialogSetModal a
self Bool
modal = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let modal' :: CInt
modal' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
modal
    Ptr PrintDialog -> CInt -> IO ()
gtk_print_dialog_set_modal Ptr PrintDialog
self' CInt
modal'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintDialogSetModalMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintDialog a) => O.OverloadedMethod PrintDialogSetModalMethodInfo a signature where
    overloadedMethod = printDialogSetModal

instance O.OverloadedMethodInfo PrintDialogSetModalMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogSetModal",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogSetModal"
        })


#endif

-- method PrintDialog::set_page_setup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "page_setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new page setup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_set_page_setup" gtk_print_dialog_set_page_setup :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    Ptr Gtk.PageSetup.PageSetup ->          -- page_setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    IO ()

-- | Set the page setup for the print dialog.
-- 
-- /Since: 4.14/
printDialogSetPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a, Gtk.PageSetup.IsPageSetup b) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> b
    -- ^ /@pageSetup@/: the new page setup
    -> m ()
printDialogSetPageSetup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintDialog a, IsPageSetup b) =>
a -> b -> m ()
printDialogSetPageSetup a
self b
pageSetup = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr PageSetup
pageSetup' <- b -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
pageSetup
    Ptr PrintDialog -> Ptr PageSetup -> IO ()
gtk_print_dialog_set_page_setup Ptr PrintDialog
self' Ptr PageSetup
pageSetup'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
pageSetup
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintDialogSetPageSetupMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPrintDialog a, Gtk.PageSetup.IsPageSetup b) => O.OverloadedMethod PrintDialogSetPageSetupMethodInfo a signature where
    overloadedMethod = printDialogSetPageSetup

instance O.OverloadedMethodInfo PrintDialogSetPageSetupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogSetPageSetup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogSetPageSetup"
        })


#endif

-- method PrintDialog::set_print_settings
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "print_settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new print settings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_set_print_settings" gtk_print_dialog_set_print_settings :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    Ptr Gtk.PrintSettings.PrintSettings ->  -- print_settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO ()

-- | Sets the print settings for the print dialog.
-- 
-- /Since: 4.14/
printDialogSetPrintSettings ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a, Gtk.PrintSettings.IsPrintSettings b) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> b
    -- ^ /@printSettings@/: the new print settings
    -> m ()
printDialogSetPrintSettings :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintDialog a, IsPrintSettings b) =>
a -> b -> m ()
printDialogSetPrintSettings a
self b
printSettings = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr PrintSettings
printSettings' <- b -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
printSettings
    Ptr PrintDialog -> Ptr PrintSettings -> IO ()
gtk_print_dialog_set_print_settings Ptr PrintDialog
self' Ptr PrintSettings
printSettings'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
printSettings
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintDialogSetPrintSettingsMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPrintDialog a, Gtk.PrintSettings.IsPrintSettings b) => O.OverloadedMethod PrintDialogSetPrintSettingsMethodInfo a signature where
    overloadedMethod = printDialogSetPrintSettings

instance O.OverloadedMethodInfo PrintDialogSetPrintSettingsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogSetPrintSettings",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogSetPrintSettings"
        })


#endif

-- method PrintDialog::set_title
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "title"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new title" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_set_title" gtk_print_dialog_set_title :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    CString ->                              -- title : TBasicType TUTF8
    IO ()

-- | Sets the title that will be shown on the print dialog.
-- 
-- /Since: 4.14/
printDialogSetTitle ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> T.Text
    -- ^ /@title@/: the new title
    -> m ()
printDialogSetTitle :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintDialog a) =>
a -> Text -> m ()
printDialogSetTitle a
self Text
title = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CString
title' <- Text -> IO CString
textToCString Text
title
    Ptr PrintDialog -> CString -> IO ()
gtk_print_dialog_set_title Ptr PrintDialog
self' CString
title'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
title'
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintDialogSetTitleMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintDialog a) => O.OverloadedMethod PrintDialogSetTitleMethodInfo a signature where
    overloadedMethod = printDialogSetTitle

instance O.OverloadedMethodInfo PrintDialogSetTitleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogSetTitle",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogSetTitle"
        })


#endif

-- method PrintDialog::setup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the parent `GtkWindow`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "cancellable"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "Cancellable" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GCancellable` to cancel the operation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "callback"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncReadyCallback" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "a callback to call when the operation is complete"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeAsync
--           , argClosure = 4
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "data to pass to @callback"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_dialog_setup" gtk_print_dialog_setup :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    Ptr Gtk.Window.Window ->                -- parent : TInterface (Name {namespace = "Gtk", name = "Window"})
    Ptr Gio.Cancellable.Cancellable ->      -- cancellable : TInterface (Name {namespace = "Gio", name = "Cancellable"})
    FunPtr Gio.Callbacks.C_AsyncReadyCallback -> -- callback : TInterface (Name {namespace = "Gio", name = "AsyncReadyCallback"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | This function presents a print dialog to let the user select a printer,
-- and set up print settings and page setup.
-- 
-- The /@callback@/ will be called when the dialog is dismissed.
-- It should call 'GI.Gtk.Objects.PrintDialog.printDialogSetupFinish'
-- to obtain the results in the form of a [struct/@gtk@/.PrintSetup],
-- that can then be passed to 'GI.Gtk.Objects.PrintDialog.printDialogPrint'
-- or 'GI.Gtk.Objects.PrintDialog.printDialogPrintFile'.
-- 
-- One possible use for this method is to have the user select a printer,
-- then show a page setup UI in the application (e.g. to arrange images
-- on a page), then call 'GI.Gtk.Objects.PrintDialog.printDialogPrint' on /@self@/
-- to do the printing without further user interaction.
-- 
-- /Since: 4.14/
printDialogSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> Maybe (b)
    -- ^ /@parent@/: the parent @GtkWindow@
    -> Maybe (c)
    -- ^ /@cancellable@/: a @GCancellable@ to cancel the operation
    -> Maybe (Gio.Callbacks.AsyncReadyCallback)
    -- ^ /@callback@/: a callback to call when the operation is complete
    -> m ()
printDialogSetup :: forall (m :: * -> *) a b c.
(HasCallStack, MonadIO m, IsPrintDialog a, IsWindow b,
 IsCancellable c) =>
a -> Maybe b -> Maybe c -> Maybe AsyncReadyCallback -> m ()
printDialogSetup a
self Maybe b
parent Maybe c
cancellable Maybe AsyncReadyCallback
callback = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr Window
maybeParent <- case Maybe b
parent of
        Maybe b
Nothing -> Ptr Window -> IO (Ptr Window)
forall a. a -> IO a
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 a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Window
jParent'
    Ptr Cancellable
maybeCancellable <- case Maybe c
cancellable of
        Maybe c
Nothing -> Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
forall a. Ptr a
nullPtr
        Just c
jCancellable -> do
            Ptr Cancellable
jCancellable' <- c -> IO (Ptr Cancellable)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr c
jCancellable
            Ptr Cancellable -> IO (Ptr Cancellable)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Cancellable
jCancellable'
    FunPtr C_AsyncReadyCallback
maybeCallback <- case Maybe AsyncReadyCallback
callback of
        Maybe AsyncReadyCallback
Nothing -> FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Any -> FunPtr C_AsyncReadyCallback
forall a b. Ptr a -> FunPtr b
castPtrToFunPtr Ptr Any
forall a. Ptr a
nullPtr)
        Just AsyncReadyCallback
jCallback -> do
            Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback <- IO (Ptr (FunPtr C_AsyncReadyCallback))
forall a. Storable a => IO (Ptr a)
callocMem :: IO (Ptr (FunPtr Gio.Callbacks.C_AsyncReadyCallback))
            FunPtr C_AsyncReadyCallback
jCallback' <- C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
Gio.Callbacks.mk_AsyncReadyCallback (Maybe (Ptr (FunPtr C_AsyncReadyCallback))
-> AsyncReadyCallback_WithClosures -> C_AsyncReadyCallback
Gio.Callbacks.wrap_AsyncReadyCallback (Ptr (FunPtr C_AsyncReadyCallback)
-> Maybe (Ptr (FunPtr C_AsyncReadyCallback))
forall a. a -> Maybe a
Just Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback) (AsyncReadyCallback -> AsyncReadyCallback_WithClosures
Gio.Callbacks.drop_closures_AsyncReadyCallback AsyncReadyCallback
jCallback))
            Ptr (FunPtr C_AsyncReadyCallback)
-> FunPtr C_AsyncReadyCallback -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (FunPtr C_AsyncReadyCallback)
ptrcallback FunPtr C_AsyncReadyCallback
jCallback'
            FunPtr C_AsyncReadyCallback -> IO (FunPtr C_AsyncReadyCallback)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return FunPtr C_AsyncReadyCallback
jCallback'
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr PrintDialog
-> Ptr Window
-> Ptr Cancellable
-> FunPtr C_AsyncReadyCallback
-> Ptr ()
-> IO ()
gtk_print_dialog_setup Ptr PrintDialog
self' Ptr Window
maybeParent Ptr Cancellable
maybeCancellable FunPtr C_AsyncReadyCallback
maybeCallback Ptr ()
forall a. Ptr a
userData
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    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
    Maybe c -> (c -> IO ()) -> IO ()
forall (m :: * -> *) a. Monad m => Maybe a -> (a -> m ()) -> m ()
whenJust Maybe c
cancellable c -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintDialogSetupMethodInfo
instance (signature ~ (Maybe (b) -> Maybe (c) -> Maybe (Gio.Callbacks.AsyncReadyCallback) -> m ()), MonadIO m, IsPrintDialog a, Gtk.Window.IsWindow b, Gio.Cancellable.IsCancellable c) => O.OverloadedMethod PrintDialogSetupMethodInfo a signature where
    overloadedMethod = printDialogSetup

instance O.OverloadedMethodInfo PrintDialogSetupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogSetup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogSetup"
        })


#endif

-- method PrintDialog::setup_finish
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDialog" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintDialog`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "result"
--           , argType =
--               TInterface Name { namespace = "Gio" , name = "AsyncResult" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GAsyncResult`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , argCallbackUserData = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "PrintSetup" })
-- throws : True
-- Skip return : False

foreign import ccall "gtk_print_dialog_setup_finish" gtk_print_dialog_setup_finish :: 
    Ptr PrintDialog ->                      -- self : TInterface (Name {namespace = "Gtk", name = "PrintDialog"})
    Ptr Gio.AsyncResult.AsyncResult ->      -- result : TInterface (Name {namespace = "Gio", name = "AsyncResult"})
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr Gtk.PrintSetup.PrintSetup)

-- | Finishes the 'GI.Gtk.Objects.PrintDialog.printDialogSetup' call.
-- 
-- If the call was successful, it returns a [struct/@gtk@/.PrintSetup]
-- which contains the print settings and page setup information that
-- will be used to print.
-- 
-- /Since: 4.14/
printDialogSetupFinish ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintDialog a, Gio.AsyncResult.IsAsyncResult b) =>
    a
    -- ^ /@self@/: a @GtkPrintDialog@
    -> b
    -- ^ /@result@/: a @GAsyncResult@
    -> m (Maybe Gtk.PrintSetup.PrintSetup)
    -- ^ __Returns:__ The @GtkPrintSetup@ object that resulted from the call,
    --   or @NULL@ if the call was not successful /(Can throw 'Data.GI.Base.GError.GError')/
printDialogSetupFinish :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintDialog a, IsAsyncResult b) =>
a -> b -> m (Maybe PrintSetup)
printDialogSetupFinish a
self b
result_ = IO (Maybe PrintSetup) -> m (Maybe PrintSetup)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PrintSetup) -> m (Maybe PrintSetup))
-> IO (Maybe PrintSetup) -> m (Maybe PrintSetup)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintDialog
self' <- a -> IO (Ptr PrintDialog)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr AsyncResult
result_' <- b -> IO (Ptr AsyncResult)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
result_
    IO (Maybe PrintSetup) -> IO () -> IO (Maybe PrintSetup)
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr PrintSetup
result <- (Ptr (Ptr GError) -> IO (Ptr PrintSetup)) -> IO (Ptr PrintSetup)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr PrintSetup)) -> IO (Ptr PrintSetup))
-> (Ptr (Ptr GError) -> IO (Ptr PrintSetup)) -> IO (Ptr PrintSetup)
forall a b. (a -> b) -> a -> b
$ Ptr PrintDialog
-> Ptr AsyncResult -> Ptr (Ptr GError) -> IO (Ptr PrintSetup)
gtk_print_dialog_setup_finish Ptr PrintDialog
self' Ptr AsyncResult
result_'
        Maybe PrintSetup
maybeResult <- Ptr PrintSetup
-> (Ptr PrintSetup -> IO PrintSetup) -> IO (Maybe PrintSetup)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PrintSetup
result ((Ptr PrintSetup -> IO PrintSetup) -> IO (Maybe PrintSetup))
-> (Ptr PrintSetup -> IO PrintSetup) -> IO (Maybe PrintSetup)
forall a b. (a -> b) -> a -> b
$ \Ptr PrintSetup
result' -> do
            PrintSetup
result'' <- ((ManagedPtr PrintSetup -> PrintSetup)
-> Ptr PrintSetup -> IO PrintSetup
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr PrintSetup -> PrintSetup
Gtk.PrintSetup.PrintSetup) Ptr PrintSetup
result'
            PrintSetup -> IO PrintSetup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSetup
result''
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
        b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
result_
        Maybe PrintSetup -> IO (Maybe PrintSetup)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PrintSetup
maybeResult
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data PrintDialogSetupFinishMethodInfo
instance (signature ~ (b -> m (Maybe Gtk.PrintSetup.PrintSetup)), MonadIO m, IsPrintDialog a, Gio.AsyncResult.IsAsyncResult b) => O.OverloadedMethod PrintDialogSetupFinishMethodInfo a signature where
    overloadedMethod = printDialogSetupFinish

instance O.OverloadedMethodInfo PrintDialogSetupFinishMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Objects.PrintDialog.printDialogSetupFinish",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Objects-PrintDialog.html#v:printDialogSetupFinish"
        })


#endif