{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Controls a print operation.
-- 
-- A t'GI.WebKit2.Objects.PrintOperation.PrintOperation' controls a print operation in WebKit. With
-- a similar API to t'GI.Gtk.Objects.PrintOperation.PrintOperation', it lets you set the print
-- settings with 'GI.WebKit2.Objects.PrintOperation.printOperationSetPrintSettings' or
-- display the print dialog with 'GI.WebKit2.Objects.PrintOperation.printOperationRunDialog'.

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

module GI.WebKit2.Objects.PrintOperation
    ( 

-- * Exported types
    PrintOperation(..)                      ,
    IsPrintOperation                        ,
    toPrintOperation                        ,


 -- * 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.WebKit2.Objects.PrintOperation#g:method:print"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDialog]("GI.WebKit2.Objects.PrintOperation#g:method:runDialog"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getPageSetup]("GI.WebKit2.Objects.PrintOperation#g:method:getPageSetup"), [getPrintSettings]("GI.WebKit2.Objects.PrintOperation#g:method:getPrintSettings"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setPageSetup]("GI.WebKit2.Objects.PrintOperation#g:method:setPageSetup"), [setPrintSettings]("GI.WebKit2.Objects.PrintOperation#g:method:setPrintSettings"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolvePrintOperationMethod             ,
#endif

-- ** getPageSetup #method:getPageSetup#

#if defined(ENABLE_OVERLOADING)
    PrintOperationGetPageSetupMethodInfo    ,
#endif
    printOperationGetPageSetup              ,


-- ** getPrintSettings #method:getPrintSettings#

#if defined(ENABLE_OVERLOADING)
    PrintOperationGetPrintSettingsMethodInfo,
#endif
    printOperationGetPrintSettings          ,


-- ** new #method:new#

    printOperationNew                       ,


-- ** print #method:print#

#if defined(ENABLE_OVERLOADING)
    PrintOperationPrintMethodInfo           ,
#endif
    printOperationPrint                     ,


-- ** runDialog #method:runDialog#

#if defined(ENABLE_OVERLOADING)
    PrintOperationRunDialogMethodInfo       ,
#endif
    printOperationRunDialog                 ,


-- ** setPageSetup #method:setPageSetup#

#if defined(ENABLE_OVERLOADING)
    PrintOperationSetPageSetupMethodInfo    ,
#endif
    printOperationSetPageSetup              ,


-- ** setPrintSettings #method:setPrintSettings#

#if defined(ENABLE_OVERLOADING)
    PrintOperationSetPrintSettingsMethodInfo,
#endif
    printOperationSetPrintSettings          ,




 -- * Properties


-- ** pageSetup #attr:pageSetup#
-- | The initial t'GI.Gtk.Objects.PageSetup.PageSetup' for the print operation.

#if defined(ENABLE_OVERLOADING)
    PrintOperationPageSetupPropertyInfo     ,
#endif
    constructPrintOperationPageSetup        ,
    getPrintOperationPageSetup              ,
#if defined(ENABLE_OVERLOADING)
    printOperationPageSetup                 ,
#endif
    setPrintOperationPageSetup              ,


-- ** printSettings #attr:printSettings#
-- | The initial t'GI.Gtk.Objects.PrintSettings.PrintSettings' for the print operation.

#if defined(ENABLE_OVERLOADING)
    PrintOperationPrintSettingsPropertyInfo ,
#endif
    constructPrintOperationPrintSettings    ,
    getPrintOperationPrintSettings          ,
#if defined(ENABLE_OVERLOADING)
    printOperationPrintSettings             ,
#endif
    setPrintOperationPrintSettings          ,


-- ** webView #attr:webView#
-- | The t'GI.WebKit2.Objects.WebView.WebView' that will be printed.

#if defined(ENABLE_OVERLOADING)
    PrintOperationWebViewPropertyInfo       ,
#endif
    constructPrintOperationWebView          ,
    getPrintOperationWebView                ,
#if defined(ENABLE_OVERLOADING)
    printOperationWebView                   ,
#endif




 -- * Signals


-- ** createCustomWidget #signal:createCustomWidget#

    PrintOperationCreateCustomWidgetCallback,
#if defined(ENABLE_OVERLOADING)
    PrintOperationCreateCustomWidgetSignalInfo,
#endif
    afterPrintOperationCreateCustomWidget   ,
    onPrintOperationCreateCustomWidget      ,


-- ** failed #signal:failed#

    PrintOperationFailedCallback            ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationFailedSignalInfo          ,
#endif
    afterPrintOperationFailed               ,
    onPrintOperationFailed                  ,


-- ** finished #signal:finished#

    PrintOperationFinishedCallback          ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationFinishedSignalInfo        ,
#endif
    afterPrintOperationFinished             ,
    onPrintOperationFinished                ,




    ) 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.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R

import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings
import qualified GI.Gtk.Objects.Window as Gtk.Window
import {-# SOURCE #-} qualified GI.WebKit2.Enums as WebKit2.Enums
import {-# SOURCE #-} qualified GI.WebKit2.Objects.PrintCustomWidget as WebKit2.PrintCustomWidget
import {-# SOURCE #-} qualified GI.WebKit2.Objects.WebView as WebKit2.WebView

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

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

foreign import ccall "webkit_print_operation_get_type"
    c_webkit_print_operation_get_type :: IO B.Types.GType

instance B.Types.TypedObject PrintOperation where
    glibType :: IO GType
glibType = IO GType
c_webkit_print_operation_get_type

instance B.Types.GObject PrintOperation

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

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

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

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

#if defined(ENABLE_OVERLOADING)
type family ResolvePrintOperationMethod (t :: Symbol) (o :: *) :: * where
    ResolvePrintOperationMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePrintOperationMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePrintOperationMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePrintOperationMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePrintOperationMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePrintOperationMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePrintOperationMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePrintOperationMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePrintOperationMethod "print" o = PrintOperationPrintMethodInfo
    ResolvePrintOperationMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePrintOperationMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePrintOperationMethod "runDialog" o = PrintOperationRunDialogMethodInfo
    ResolvePrintOperationMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePrintOperationMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePrintOperationMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePrintOperationMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePrintOperationMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePrintOperationMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePrintOperationMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePrintOperationMethod "getPageSetup" o = PrintOperationGetPageSetupMethodInfo
    ResolvePrintOperationMethod "getPrintSettings" o = PrintOperationGetPrintSettingsMethodInfo
    ResolvePrintOperationMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePrintOperationMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePrintOperationMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePrintOperationMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePrintOperationMethod "setPageSetup" o = PrintOperationSetPageSetupMethodInfo
    ResolvePrintOperationMethod "setPrintSettings" o = PrintOperationSetPrintSettingsMethodInfo
    ResolvePrintOperationMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePrintOperationMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePrintOperationMethod t PrintOperation, O.OverloadedMethod info PrintOperation p) => OL.IsLabel t (PrintOperation -> p) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.overloadedMethod @info
#else
    fromLabel _ = O.overloadedMethod @info
#endif

#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolvePrintOperationMethod t PrintOperation, O.OverloadedMethod info PrintOperation p, R.HasField t PrintOperation p) => R.HasField t PrintOperation p where
    getField = O.overloadedMethod @info

#endif

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

#endif

-- signal PrintOperation::create-custom-widget
-- | Emitted when displaying the print dialog with 'GI.WebKit2.Objects.PrintOperation.printOperationRunDialog'.
-- The returned t'GI.WebKit2.Objects.PrintCustomWidget.PrintCustomWidget' will be added to the print dialog and
-- it will be owned by the /@printOperation@/. However, the object is guaranteed
-- to be alive until the [PrintCustomWidget::apply]("GI.WebKit2.Objects.PrintCustomWidget#g:signal:apply") is emitted.
-- 
-- /Since: 2.16/
type PrintOperationCreateCustomWidgetCallback =
    IO WebKit2.PrintCustomWidget.PrintCustomWidget
    -- ^ __Returns:__ A t'GI.WebKit2.Objects.PrintCustomWidget.PrintCustomWidget' that will be embedded in the dialog.

type C_PrintOperationCreateCustomWidgetCallback =
    Ptr PrintOperation ->                   -- object
    Ptr () ->                               -- user_data
    IO (Ptr WebKit2.PrintCustomWidget.PrintCustomWidget)

-- | Generate a function pointer callable from C code, from a `C_PrintOperationCreateCustomWidgetCallback`.
foreign import ccall "wrapper"
    mk_PrintOperationCreateCustomWidgetCallback :: C_PrintOperationCreateCustomWidgetCallback -> IO (FunPtr C_PrintOperationCreateCustomWidgetCallback)

wrap_PrintOperationCreateCustomWidgetCallback :: 
    GObject a => (a -> PrintOperationCreateCustomWidgetCallback) ->
    C_PrintOperationCreateCustomWidgetCallback
wrap_PrintOperationCreateCustomWidgetCallback :: forall a.
GObject a =>
(a -> PrintOperationCreateCustomWidgetCallback)
-> C_PrintOperationCreateCustomWidgetCallback
wrap_PrintOperationCreateCustomWidgetCallback a -> PrintOperationCreateCustomWidgetCallback
gi'cb Ptr PrintOperation
gi'selfPtr Ptr ()
_ = do
    PrintCustomWidget
result <- Ptr PrintOperation
-> (PrintOperation -> PrintOperationCreateCustomWidgetCallback)
-> PrintOperationCreateCustomWidgetCallback
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr PrintOperation
gi'selfPtr ((PrintOperation -> PrintOperationCreateCustomWidgetCallback)
 -> PrintOperationCreateCustomWidgetCallback)
-> (PrintOperation -> PrintOperationCreateCustomWidgetCallback)
-> PrintOperationCreateCustomWidgetCallback
forall a b. (a -> b) -> a -> b
$ \PrintOperation
gi'self -> a -> PrintOperationCreateCustomWidgetCallback
gi'cb (PrintOperation -> a
forall a b. Coercible a b => a -> b
Coerce.coerce PrintOperation
gi'self) 
    Ptr PrintCustomWidget
result' <- PrintCustomWidget -> IO (Ptr PrintCustomWidget)
forall a b. (HasCallStack, GObject a) => a -> IO (Ptr b)
B.ManagedPtr.disownObject PrintCustomWidget
result
    Ptr PrintCustomWidget -> IO (Ptr PrintCustomWidget)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr PrintCustomWidget
result'


-- | Connect a signal handler for the [createCustomWidget](#signal:createCustomWidget) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' printOperation #createCustomWidget callback
-- @
-- 
-- 
onPrintOperationCreateCustomWidget :: (IsPrintOperation a, MonadIO m) => a -> ((?self :: a) => PrintOperationCreateCustomWidgetCallback) -> m SignalHandlerId
onPrintOperationCreateCustomWidget :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a
-> ((?self::a) => PrintOperationCreateCustomWidgetCallback)
-> m SignalHandlerId
onPrintOperationCreateCustomWidget a
obj (?self::a) => PrintOperationCreateCustomWidgetCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PrintOperationCreateCustomWidgetCallback
wrapped a
self = let ?self = a
?self::a
self in PrintOperationCreateCustomWidgetCallback
(?self::a) => PrintOperationCreateCustomWidgetCallback
cb
    let wrapped' :: C_PrintOperationCreateCustomWidgetCallback
wrapped' = (a -> PrintOperationCreateCustomWidgetCallback)
-> C_PrintOperationCreateCustomWidgetCallback
forall a.
GObject a =>
(a -> PrintOperationCreateCustomWidgetCallback)
-> C_PrintOperationCreateCustomWidgetCallback
wrap_PrintOperationCreateCustomWidgetCallback a -> PrintOperationCreateCustomWidgetCallback
wrapped
    FunPtr C_PrintOperationCreateCustomWidgetCallback
wrapped'' <- C_PrintOperationCreateCustomWidgetCallback
-> IO (FunPtr C_PrintOperationCreateCustomWidgetCallback)
mk_PrintOperationCreateCustomWidgetCallback C_PrintOperationCreateCustomWidgetCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationCreateCustomWidgetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"create-custom-widget" FunPtr C_PrintOperationCreateCustomWidgetCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [createCustomWidget](#signal:createCustomWidget) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' printOperation #createCustomWidget callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterPrintOperationCreateCustomWidget :: (IsPrintOperation a, MonadIO m) => a -> ((?self :: a) => PrintOperationCreateCustomWidgetCallback) -> m SignalHandlerId
afterPrintOperationCreateCustomWidget :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a
-> ((?self::a) => PrintOperationCreateCustomWidgetCallback)
-> m SignalHandlerId
afterPrintOperationCreateCustomWidget a
obj (?self::a) => PrintOperationCreateCustomWidgetCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PrintOperationCreateCustomWidgetCallback
wrapped a
self = let ?self = a
?self::a
self in PrintOperationCreateCustomWidgetCallback
(?self::a) => PrintOperationCreateCustomWidgetCallback
cb
    let wrapped' :: C_PrintOperationCreateCustomWidgetCallback
wrapped' = (a -> PrintOperationCreateCustomWidgetCallback)
-> C_PrintOperationCreateCustomWidgetCallback
forall a.
GObject a =>
(a -> PrintOperationCreateCustomWidgetCallback)
-> C_PrintOperationCreateCustomWidgetCallback
wrap_PrintOperationCreateCustomWidgetCallback a -> PrintOperationCreateCustomWidgetCallback
wrapped
    FunPtr C_PrintOperationCreateCustomWidgetCallback
wrapped'' <- C_PrintOperationCreateCustomWidgetCallback
-> IO (FunPtr C_PrintOperationCreateCustomWidgetCallback)
mk_PrintOperationCreateCustomWidgetCallback C_PrintOperationCreateCustomWidgetCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationCreateCustomWidgetCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"create-custom-widget" FunPtr C_PrintOperationCreateCustomWidgetCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PrintOperationCreateCustomWidgetSignalInfo
instance SignalInfo PrintOperationCreateCustomWidgetSignalInfo where
    type HaskellCallbackType PrintOperationCreateCustomWidgetSignalInfo = PrintOperationCreateCustomWidgetCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationCreateCustomWidgetCallback cb
        cb'' <- mk_PrintOperationCreateCustomWidgetCallback cb'
        connectSignalFunPtr obj "create-custom-widget" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation::create-custom-widget"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#g:signal:createCustomWidget"})

#endif

-- signal PrintOperation::failed
-- | Emitted when an error occurs while printing. The given /@error@/, of the domain
-- @/WEBKIT_PRINT_ERROR/@, contains further details of the failure.
-- The [PrintOperation::finished]("GI.WebKit2.Objects.PrintOperation#g:signal:finished") signal is emitted after this one.
type PrintOperationFailedCallback =
    GError
    -- ^ /@error@/: the t'GError' that was triggered
    -> IO ()

type C_PrintOperationFailedCallback =
    Ptr PrintOperation ->                   -- object
    Ptr GError ->
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_PrintOperationFailedCallback`.
foreign import ccall "wrapper"
    mk_PrintOperationFailedCallback :: C_PrintOperationFailedCallback -> IO (FunPtr C_PrintOperationFailedCallback)

wrap_PrintOperationFailedCallback :: 
    GObject a => (a -> PrintOperationFailedCallback) ->
    C_PrintOperationFailedCallback
wrap_PrintOperationFailedCallback :: forall a.
GObject a =>
(a -> PrintOperationFailedCallback)
-> C_PrintOperationFailedCallback
wrap_PrintOperationFailedCallback a -> PrintOperationFailedCallback
gi'cb Ptr PrintOperation
gi'selfPtr Ptr GError
error_ Ptr ()
_ = do
    GError
error_' <- ((ManagedPtr GError -> GError) -> Ptr GError -> IO GError
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr GError -> GError
GError) Ptr GError
error_
    Ptr PrintOperation -> (PrintOperation -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr PrintOperation
gi'selfPtr ((PrintOperation -> IO ()) -> IO ())
-> (PrintOperation -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \PrintOperation
gi'self -> a -> PrintOperationFailedCallback
gi'cb (PrintOperation -> a
forall a b. Coercible a b => a -> b
Coerce.coerce PrintOperation
gi'self)  GError
error_'


-- | Connect a signal handler for the [failed](#signal:failed) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' printOperation #failed callback
-- @
-- 
-- 
onPrintOperationFailed :: (IsPrintOperation a, MonadIO m) => a -> ((?self :: a) => PrintOperationFailedCallback) -> m SignalHandlerId
onPrintOperationFailed :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a
-> ((?self::a) => PrintOperationFailedCallback)
-> m SignalHandlerId
onPrintOperationFailed a
obj (?self::a) => PrintOperationFailedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PrintOperationFailedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PrintOperationFailedCallback
PrintOperationFailedCallback
cb
    let wrapped' :: C_PrintOperationFailedCallback
wrapped' = (a -> PrintOperationFailedCallback)
-> C_PrintOperationFailedCallback
forall a.
GObject a =>
(a -> PrintOperationFailedCallback)
-> C_PrintOperationFailedCallback
wrap_PrintOperationFailedCallback a -> PrintOperationFailedCallback
wrapped
    FunPtr C_PrintOperationFailedCallback
wrapped'' <- C_PrintOperationFailedCallback
-> IO (FunPtr C_PrintOperationFailedCallback)
mk_PrintOperationFailedCallback C_PrintOperationFailedCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationFailedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"failed" FunPtr C_PrintOperationFailedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [failed](#signal:failed) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' printOperation #failed callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterPrintOperationFailed :: (IsPrintOperation a, MonadIO m) => a -> ((?self :: a) => PrintOperationFailedCallback) -> m SignalHandlerId
afterPrintOperationFailed :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a
-> ((?self::a) => PrintOperationFailedCallback)
-> m SignalHandlerId
afterPrintOperationFailed a
obj (?self::a) => PrintOperationFailedCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PrintOperationFailedCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PrintOperationFailedCallback
PrintOperationFailedCallback
cb
    let wrapped' :: C_PrintOperationFailedCallback
wrapped' = (a -> PrintOperationFailedCallback)
-> C_PrintOperationFailedCallback
forall a.
GObject a =>
(a -> PrintOperationFailedCallback)
-> C_PrintOperationFailedCallback
wrap_PrintOperationFailedCallback a -> PrintOperationFailedCallback
wrapped
    FunPtr C_PrintOperationFailedCallback
wrapped'' <- C_PrintOperationFailedCallback
-> IO (FunPtr C_PrintOperationFailedCallback)
mk_PrintOperationFailedCallback C_PrintOperationFailedCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationFailedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"failed" FunPtr C_PrintOperationFailedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PrintOperationFailedSignalInfo
instance SignalInfo PrintOperationFailedSignalInfo where
    type HaskellCallbackType PrintOperationFailedSignalInfo = PrintOperationFailedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationFailedCallback cb
        cb'' <- mk_PrintOperationFailedCallback cb'
        connectSignalFunPtr obj "failed" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation::failed"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#g:signal:failed"})

#endif

-- signal PrintOperation::finished
-- | Emitted when the print operation has finished doing everything
-- required for printing.
type PrintOperationFinishedCallback =
    IO ()

type C_PrintOperationFinishedCallback =
    Ptr PrintOperation ->                   -- object
    Ptr () ->                               -- user_data
    IO ()

-- | Generate a function pointer callable from C code, from a `C_PrintOperationFinishedCallback`.
foreign import ccall "wrapper"
    mk_PrintOperationFinishedCallback :: C_PrintOperationFinishedCallback -> IO (FunPtr C_PrintOperationFinishedCallback)

wrap_PrintOperationFinishedCallback :: 
    GObject a => (a -> PrintOperationFinishedCallback) ->
    C_PrintOperationFinishedCallback
wrap_PrintOperationFinishedCallback :: forall a.
GObject a =>
(a -> IO ()) -> C_PrintOperationFinishedCallback
wrap_PrintOperationFinishedCallback a -> IO ()
gi'cb Ptr PrintOperation
gi'selfPtr Ptr ()
_ = do
    Ptr PrintOperation -> (PrintOperation -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr PrintOperation
gi'selfPtr ((PrintOperation -> IO ()) -> IO ())
-> (PrintOperation -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \PrintOperation
gi'self -> a -> IO ()
gi'cb (PrintOperation -> a
forall a b. Coercible a b => a -> b
Coerce.coerce PrintOperation
gi'self) 


-- | Connect a signal handler for the [finished](#signal:finished) signal, to be run before the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.on' printOperation #finished callback
-- @
-- 
-- 
onPrintOperationFinished :: (IsPrintOperation a, MonadIO m) => a -> ((?self :: a) => PrintOperationFinishedCallback) -> m SignalHandlerId
onPrintOperationFinished :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
onPrintOperationFinished a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_PrintOperationFinishedCallback
wrapped' = (a -> IO ()) -> C_PrintOperationFinishedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_PrintOperationFinishedCallback
wrap_PrintOperationFinishedCallback a -> IO ()
wrapped
    FunPtr C_PrintOperationFinishedCallback
wrapped'' <- C_PrintOperationFinishedCallback
-> IO (FunPtr C_PrintOperationFinishedCallback)
mk_PrintOperationFinishedCallback C_PrintOperationFinishedCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationFinishedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"finished" FunPtr C_PrintOperationFinishedCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [finished](#signal:finished) signal, to be run after the default handler.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Signals.after' printOperation #finished callback
-- @
-- 
-- 
-- 
-- By default the object invoking the signal is not passed to the callback.
-- If you need to access it, you can use the implit @?self@ parameter.
-- Note that this requires activating the @ImplicitParams@ GHC extension.
-- 
afterPrintOperationFinished :: (IsPrintOperation a, MonadIO m) => a -> ((?self :: a) => PrintOperationFinishedCallback) -> m SignalHandlerId
afterPrintOperationFinished :: forall a (m :: * -> *).
(IsPrintOperation a, MonadIO m) =>
a -> ((?self::a) => IO ()) -> m SignalHandlerId
afterPrintOperationFinished a
obj (?self::a) => IO ()
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> IO ()
wrapped a
self = let ?self = a
?self::a
self in IO ()
(?self::a) => IO ()
cb
    let wrapped' :: C_PrintOperationFinishedCallback
wrapped' = (a -> IO ()) -> C_PrintOperationFinishedCallback
forall a.
GObject a =>
(a -> IO ()) -> C_PrintOperationFinishedCallback
wrap_PrintOperationFinishedCallback a -> IO ()
wrapped
    FunPtr C_PrintOperationFinishedCallback
wrapped'' <- C_PrintOperationFinishedCallback
-> IO (FunPtr C_PrintOperationFinishedCallback)
mk_PrintOperationFinishedCallback C_PrintOperationFinishedCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationFinishedCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"finished" FunPtr C_PrintOperationFinishedCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PrintOperationFinishedSignalInfo
instance SignalInfo PrintOperationFinishedSignalInfo where
    type HaskellCallbackType PrintOperationFinishedSignalInfo = PrintOperationFinishedCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationFinishedCallback cb
        cb'' <- mk_PrintOperationFinishedCallback cb'
        connectSignalFunPtr obj "finished" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation::finished"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#g:signal:finished"})

#endif

-- VVV Prop "page-setup"
   -- Type: TInterface (Name {namespace = "Gtk", name = "PageSetup"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,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' printOperation #pageSetup
-- @
getPrintOperationPageSetup :: (MonadIO m, IsPrintOperation o) => o -> m (Maybe Gtk.PageSetup.PageSetup)
getPrintOperationPageSetup :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m (Maybe PageSetup)
getPrintOperationPageSetup o
obj = IO (Maybe PageSetup) -> m (Maybe PageSetup)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe PageSetup) -> m (Maybe PageSetup))
-> IO (Maybe PageSetup) -> m (Maybe 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' printOperation [ #pageSetup 'Data.GI.Base.Attributes.:=' value ]
-- @
setPrintOperationPageSetup :: (MonadIO m, IsPrintOperation o, Gtk.PageSetup.IsPageSetup a) => o -> a -> m ()
setPrintOperationPageSetup :: forall (m :: * -> *) o a.
(MonadIO m, IsPrintOperation o, IsPageSetup a) =>
o -> a -> m ()
setPrintOperationPageSetup 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`.
constructPrintOperationPageSetup :: (IsPrintOperation o, MIO.MonadIO m, Gtk.PageSetup.IsPageSetup a) => a -> m (GValueConstruct o)
constructPrintOperationPageSetup :: forall o (m :: * -> *) a.
(IsPrintOperation o, MonadIO m, IsPageSetup a) =>
a -> m (GValueConstruct o)
constructPrintOperationPageSetup 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 PrintOperationPageSetupPropertyInfo
instance AttrInfo PrintOperationPageSetupPropertyInfo where
    type AttrAllowedOps PrintOperationPageSetupPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationPageSetupPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationPageSetupPropertyInfo = Gtk.PageSetup.IsPageSetup
    type AttrTransferTypeConstraint PrintOperationPageSetupPropertyInfo = Gtk.PageSetup.IsPageSetup
    type AttrTransferType PrintOperationPageSetupPropertyInfo = Gtk.PageSetup.PageSetup
    type AttrGetType PrintOperationPageSetupPropertyInfo = (Maybe Gtk.PageSetup.PageSetup)
    type AttrLabel PrintOperationPageSetupPropertyInfo = "page-setup"
    type AttrOrigin PrintOperationPageSetupPropertyInfo = PrintOperation
    attrGet = getPrintOperationPageSetup
    attrSet = setPrintOperationPageSetup
    attrTransfer _ v = do
        unsafeCastTo Gtk.PageSetup.PageSetup v
    attrConstruct = constructPrintOperationPageSetup
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation.pageSetup"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#g:attr:pageSetup"
        })
#endif

-- VVV Prop "print-settings"
   -- Type: TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just True,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' printOperation #printSettings
-- @
getPrintOperationPrintSettings :: (MonadIO m, IsPrintOperation o) => o -> m (Maybe Gtk.PrintSettings.PrintSettings)
getPrintOperationPrintSettings :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m (Maybe PrintSettings)
getPrintOperationPrintSettings o
obj = IO (Maybe PrintSettings) -> m (Maybe PrintSettings)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe PrintSettings) -> m (Maybe PrintSettings))
-> IO (Maybe PrintSettings) -> m (Maybe 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' printOperation [ #printSettings 'Data.GI.Base.Attributes.:=' value ]
-- @
setPrintOperationPrintSettings :: (MonadIO m, IsPrintOperation o, Gtk.PrintSettings.IsPrintSettings a) => o -> a -> m ()
setPrintOperationPrintSettings :: forall (m :: * -> *) o a.
(MonadIO m, IsPrintOperation o, IsPrintSettings a) =>
o -> a -> m ()
setPrintOperationPrintSettings o
obj a
val = IO () -> m ()
forall 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`.
constructPrintOperationPrintSettings :: (IsPrintOperation o, MIO.MonadIO m, Gtk.PrintSettings.IsPrintSettings a) => a -> m (GValueConstruct o)
constructPrintOperationPrintSettings :: forall o (m :: * -> *) a.
(IsPrintOperation o, MonadIO m, IsPrintSettings a) =>
a -> m (GValueConstruct o)
constructPrintOperationPrintSettings a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall 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 PrintOperationPrintSettingsPropertyInfo
instance AttrInfo PrintOperationPrintSettingsPropertyInfo where
    type AttrAllowedOps PrintOperationPrintSettingsPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint PrintOperationPrintSettingsPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationPrintSettingsPropertyInfo = Gtk.PrintSettings.IsPrintSettings
    type AttrTransferTypeConstraint PrintOperationPrintSettingsPropertyInfo = Gtk.PrintSettings.IsPrintSettings
    type AttrTransferType PrintOperationPrintSettingsPropertyInfo = Gtk.PrintSettings.PrintSettings
    type AttrGetType PrintOperationPrintSettingsPropertyInfo = (Maybe Gtk.PrintSettings.PrintSettings)
    type AttrLabel PrintOperationPrintSettingsPropertyInfo = "print-settings"
    type AttrOrigin PrintOperationPrintSettingsPropertyInfo = PrintOperation
    attrGet = getPrintOperationPrintSettings
    attrSet = setPrintOperationPrintSettings
    attrTransfer _ v = do
        unsafeCastTo Gtk.PrintSettings.PrintSettings v
    attrConstruct = constructPrintOperationPrintSettings
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation.printSettings"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#g:attr:printSettings"
        })
#endif

-- VVV Prop "web-view"
   -- Type: TInterface (Name {namespace = "WebKit2", name = "WebView"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Nothing,Nothing)

-- | Get the value of the “@web-view@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' printOperation #webView
-- @
getPrintOperationWebView :: (MonadIO m, IsPrintOperation o) => o -> m (Maybe WebKit2.WebView.WebView)
getPrintOperationWebView :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m (Maybe WebView)
getPrintOperationWebView o
obj = IO (Maybe WebView) -> m (Maybe WebView)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe WebView) -> m (Maybe WebView))
-> IO (Maybe WebView) -> m (Maybe WebView)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr WebView -> WebView) -> IO (Maybe WebView)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"web-view" ManagedPtr WebView -> WebView
WebKit2.WebView.WebView

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

#if defined(ENABLE_OVERLOADING)
data PrintOperationWebViewPropertyInfo
instance AttrInfo PrintOperationWebViewPropertyInfo where
    type AttrAllowedOps PrintOperationWebViewPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint PrintOperationWebViewPropertyInfo = IsPrintOperation
    type AttrSetTypeConstraint PrintOperationWebViewPropertyInfo = WebKit2.WebView.IsWebView
    type AttrTransferTypeConstraint PrintOperationWebViewPropertyInfo = WebKit2.WebView.IsWebView
    type AttrTransferType PrintOperationWebViewPropertyInfo = WebKit2.WebView.WebView
    type AttrGetType PrintOperationWebViewPropertyInfo = (Maybe WebKit2.WebView.WebView)
    type AttrLabel PrintOperationWebViewPropertyInfo = "web-view"
    type AttrOrigin PrintOperationWebViewPropertyInfo = PrintOperation
    attrGet = getPrintOperationWebView
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo WebKit2.WebView.WebView v
    attrConstruct = constructPrintOperationWebView
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation.webView"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#g:attr:webView"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PrintOperation
type instance O.AttributeList PrintOperation = PrintOperationAttributeList
type PrintOperationAttributeList = ('[ '("pageSetup", PrintOperationPageSetupPropertyInfo), '("printSettings", PrintOperationPrintSettingsPropertyInfo), '("webView", PrintOperationWebViewPropertyInfo)] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
printOperationPageSetup :: AttrLabelProxy "pageSetup"
printOperationPageSetup = AttrLabelProxy

printOperationPrintSettings :: AttrLabelProxy "printSettings"
printOperationPrintSettings = AttrLabelProxy

printOperationWebView :: AttrLabelProxy "webView"
printOperationWebView = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PrintOperation = PrintOperationSignalList
type PrintOperationSignalList = ('[ '("createCustomWidget", PrintOperationCreateCustomWidgetSignalInfo), '("failed", PrintOperationFailedSignalInfo), '("finished", PrintOperationFinishedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

-- method PrintOperation::new
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "web_view"
--           , argType =
--               TInterface Name { namespace = "WebKit2" , name = "WebView" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitWebView" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "WebKit2" , name = "PrintOperation" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_print_operation_new" webkit_print_operation_new :: 
    Ptr WebKit2.WebView.WebView ->          -- web_view : TInterface (Name {namespace = "WebKit2", name = "WebView"})
    IO (Ptr PrintOperation)

-- | Create a new t'GI.WebKit2.Objects.PrintOperation.PrintOperation' to print /@webView@/ contents.
printOperationNew ::
    (B.CallStack.HasCallStack, MonadIO m, WebKit2.WebView.IsWebView a) =>
    a
    -- ^ /@webView@/: a t'GI.WebKit2.Objects.WebView.WebView'
    -> m PrintOperation
    -- ^ __Returns:__ a new t'GI.WebKit2.Objects.PrintOperation.PrintOperation'.
printOperationNew :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsWebView a) =>
a -> m PrintOperation
printOperationNew a
webView = IO PrintOperation -> m PrintOperation
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintOperation -> m PrintOperation)
-> IO PrintOperation -> m PrintOperation
forall a b. (a -> b) -> a -> b
$ do
    Ptr WebView
webView' <- a -> IO (Ptr WebView)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
webView
    Ptr PrintOperation
result <- Ptr WebView -> IO (Ptr PrintOperation)
webkit_print_operation_new Ptr WebView
webView'
    Text -> Ptr PrintOperation -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printOperationNew" Ptr PrintOperation
result
    PrintOperation
result' <- ((ManagedPtr PrintOperation -> PrintOperation)
-> Ptr PrintOperation -> IO PrintOperation
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PrintOperation -> PrintOperation
PrintOperation) Ptr PrintOperation
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
webView
    PrintOperation -> IO PrintOperation
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PrintOperation
result'

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "webkit_print_operation_get_page_setup" webkit_print_operation_get_page_setup :: 
    Ptr PrintOperation ->                   -- print_operation : TInterface (Name {namespace = "WebKit2", name = "PrintOperation"})
    IO (Ptr Gtk.PageSetup.PageSetup)

-- | Return the current page setup of /@printOperation@/.
-- 
-- It returns 'P.Nothing' until
-- either 'GI.WebKit2.Objects.PrintOperation.printOperationSetPageSetup' or 'GI.WebKit2.Objects.PrintOperation.printOperationRunDialog'
-- have been called.
printOperationGetPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    -- ^ /@printOperation@/: a t'GI.WebKit2.Objects.PrintOperation.PrintOperation'
    -> m (Maybe Gtk.PageSetup.PageSetup)
    -- ^ __Returns:__ the current t'GI.Gtk.Objects.PageSetup.PageSetup' of /@printOperation@/.
printOperationGetPageSetup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m (Maybe PageSetup)
printOperationGetPageSetup a
printOperation = IO (Maybe PageSetup) -> m (Maybe PageSetup)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PageSetup) -> m (Maybe PageSetup))
-> IO (Maybe PageSetup) -> m (Maybe PageSetup)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
printOperation' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printOperation
    Ptr PageSetup
result <- Ptr PrintOperation -> IO (Ptr PageSetup)
webkit_print_operation_get_page_setup Ptr PrintOperation
printOperation'
    Maybe PageSetup
maybeResult <- Ptr PageSetup
-> (Ptr PageSetup -> IO PageSetup) -> IO (Maybe PageSetup)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PageSetup
result ((Ptr PageSetup -> IO PageSetup) -> IO (Maybe PageSetup))
-> (Ptr PageSetup -> IO PageSetup) -> IO (Maybe PageSetup)
forall a b. (a -> b) -> a -> b
$ \Ptr PageSetup
result' -> do
        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'
        PageSetup -> IO PageSetup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
printOperation
    Maybe PageSetup -> IO (Maybe PageSetup)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PageSetup
maybeResult

#if defined(ENABLE_OVERLOADING)
data PrintOperationGetPageSetupMethodInfo
instance (signature ~ (m (Maybe Gtk.PageSetup.PageSetup)), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetPageSetupMethodInfo a signature where
    overloadedMethod = printOperationGetPageSetup

instance O.OverloadedMethodInfo PrintOperationGetPageSetupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation.printOperationGetPageSetup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#v:printOperationGetPageSetup"
        })


#endif

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

foreign import ccall "webkit_print_operation_get_print_settings" webkit_print_operation_get_print_settings :: 
    Ptr PrintOperation ->                   -- print_operation : TInterface (Name {namespace = "WebKit2", name = "PrintOperation"})
    IO (Ptr Gtk.PrintSettings.PrintSettings)

-- | Return the current print settings of /@printOperation@/.
-- 
-- It returns 'P.Nothing' until
-- either 'GI.WebKit2.Objects.PrintOperation.printOperationSetPrintSettings' or 'GI.WebKit2.Objects.PrintOperation.printOperationRunDialog'
-- have been called.
printOperationGetPrintSettings ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    -- ^ /@printOperation@/: a t'GI.WebKit2.Objects.PrintOperation.PrintOperation'
    -> m (Maybe Gtk.PrintSettings.PrintSettings)
    -- ^ __Returns:__ the current t'GI.Gtk.Objects.PrintSettings.PrintSettings' of /@printOperation@/.
printOperationGetPrintSettings :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m (Maybe PrintSettings)
printOperationGetPrintSettings a
printOperation = IO (Maybe PrintSettings) -> m (Maybe PrintSettings)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PrintSettings) -> m (Maybe PrintSettings))
-> IO (Maybe PrintSettings) -> m (Maybe PrintSettings)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
printOperation' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printOperation
    Ptr PrintSettings
result <- Ptr PrintOperation -> IO (Ptr PrintSettings)
webkit_print_operation_get_print_settings Ptr PrintOperation
printOperation'
    Maybe PrintSettings
maybeResult <- Ptr PrintSettings
-> (Ptr PrintSettings -> IO PrintSettings)
-> IO (Maybe PrintSettings)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PrintSettings
result ((Ptr PrintSettings -> IO PrintSettings)
 -> IO (Maybe PrintSettings))
-> (Ptr PrintSettings -> IO PrintSettings)
-> IO (Maybe PrintSettings)
forall a b. (a -> b) -> a -> b
$ \Ptr PrintSettings
result' -> do
        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'
        PrintSettings -> IO PrintSettings
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
printOperation
    Maybe PrintSettings -> IO (Maybe PrintSettings)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PrintSettings
maybeResult

#if defined(ENABLE_OVERLOADING)
data PrintOperationGetPrintSettingsMethodInfo
instance (signature ~ (m (Maybe Gtk.PrintSettings.PrintSettings)), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetPrintSettingsMethodInfo a signature where
    overloadedMethod = printOperationGetPrintSettings

instance O.OverloadedMethodInfo PrintOperationGetPrintSettingsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation.printOperationGetPrintSettings",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#v:printOperationGetPrintSettings"
        })


#endif

-- method PrintOperation::print
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "print_operation"
--           , argType =
--               TInterface Name { namespace = "WebKit2" , name = "PrintOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitPrintOperation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_print_operation_print" webkit_print_operation_print :: 
    Ptr PrintOperation ->                   -- print_operation : TInterface (Name {namespace = "WebKit2", name = "PrintOperation"})
    IO ()

-- | Start a print operation using current print settings and page setup.
-- 
-- Start a print operation using current print settings and page setup
-- without showing the print dialog. If either print settings or page setup
-- are not set with 'GI.WebKit2.Objects.PrintOperation.printOperationSetPrintSettings' and
-- 'GI.WebKit2.Objects.PrintOperation.printOperationSetPageSetup', the default options will be used
-- and the print job will be sent to the default printer.
-- The [PrintOperation::finished]("GI.WebKit2.Objects.PrintOperation#g:signal:finished") signal is emitted when the printing
-- operation finishes. If an error occurs while printing the signal
-- [PrintOperation::failed]("GI.WebKit2.Objects.PrintOperation#g:signal:failed") is emitted before [PrintOperation::finished]("GI.WebKit2.Objects.PrintOperation#g:signal:finished").
printOperationPrint ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
    a
    -- ^ /@printOperation@/: a t'GI.WebKit2.Objects.PrintOperation.PrintOperation'
    -> m ()
printOperationPrint :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m ()
printOperationPrint a
printOperation = 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 PrintOperation
printOperation' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printOperation
    Ptr PrintOperation -> IO ()
webkit_print_operation_print Ptr PrintOperation
printOperation'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
printOperation
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintOperationPrintMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationPrintMethodInfo a signature where
    overloadedMethod = printOperationPrint

instance O.OverloadedMethodInfo PrintOperationPrintMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation.printOperationPrint",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#v:printOperationPrint"
        })


#endif

-- method PrintOperation::run_dialog
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "print_operation"
--           , argType =
--               TInterface Name { namespace = "WebKit2" , name = "PrintOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitPrintOperation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "parent"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Window" }
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "transient parent of the print dialog"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface
--                  Name { namespace = "WebKit2" , name = "PrintOperationResponse" })
-- throws : False
-- Skip return : False

foreign import ccall "webkit_print_operation_run_dialog" webkit_print_operation_run_dialog :: 
    Ptr PrintOperation ->                   -- print_operation : TInterface (Name {namespace = "WebKit2", name = "PrintOperation"})
    Ptr Gtk.Window.Window ->                -- parent : TInterface (Name {namespace = "Gtk", name = "Window"})
    IO CUInt

-- | Run the print dialog and start printing.
-- 
-- Run the print dialog and start printing using the options selected by
-- the user. This method returns when the print dialog is closed.
-- If the print dialog is cancelled 'GI.WebKit2.Enums.PrintOperationResponseCancel'
-- is returned. If the user clicks on the print button, 'GI.WebKit2.Enums.PrintOperationResponsePrint'
-- is returned and the print operation starts. In this case, the [PrintOperation::finished]("GI.WebKit2.Objects.PrintOperation#g:signal:finished")
-- signal is emitted when the operation finishes. If an error occurs while printing, the signal
-- [PrintOperation::failed]("GI.WebKit2.Objects.PrintOperation#g:signal:failed") is emitted before [PrintOperation::finished]("GI.WebKit2.Objects.PrintOperation#g:signal:finished").
-- If the print dialog is not cancelled current print settings and page setup of /@printOperation@/
-- are updated with options selected by the user when Print button is pressed in print dialog.
-- You can get the updated print settings and page setup by calling
-- 'GI.WebKit2.Objects.PrintOperation.printOperationGetPrintSettings' and 'GI.WebKit2.Objects.PrintOperation.printOperationGetPageSetup'
-- after this method.
printOperationRunDialog ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a, Gtk.Window.IsWindow b) =>
    a
    -- ^ /@printOperation@/: a t'GI.WebKit2.Objects.PrintOperation.PrintOperation'
    -> Maybe (b)
    -- ^ /@parent@/: transient parent of the print dialog
    -> m WebKit2.Enums.PrintOperationResponse
    -- ^ __Returns:__ the t'GI.WebKit2.Enums.PrintOperationResponse' of the print dialog
printOperationRunDialog :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintOperation a, IsWindow b) =>
a -> Maybe b -> m PrintOperationResponse
printOperationRunDialog a
printOperation Maybe b
parent = IO PrintOperationResponse -> m PrintOperationResponse
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintOperationResponse -> m PrintOperationResponse)
-> IO PrintOperationResponse -> m PrintOperationResponse
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperation
printOperation' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printOperation
    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'
    CUInt
result <- Ptr PrintOperation -> Ptr Window -> IO CUInt
webkit_print_operation_run_dialog Ptr PrintOperation
printOperation' Ptr Window
maybeParent
    let result' :: PrintOperationResponse
result' = (Int -> PrintOperationResponse
forall a. Enum a => Int -> a
toEnum (Int -> PrintOperationResponse)
-> (CUInt -> Int) -> CUInt -> PrintOperationResponse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral) CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
printOperation
    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
    PrintOperationResponse -> IO PrintOperationResponse
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PrintOperationResponse
result'

#if defined(ENABLE_OVERLOADING)
data PrintOperationRunDialogMethodInfo
instance (signature ~ (Maybe (b) -> m WebKit2.Enums.PrintOperationResponse), MonadIO m, IsPrintOperation a, Gtk.Window.IsWindow b) => O.OverloadedMethod PrintOperationRunDialogMethodInfo a signature where
    overloadedMethod = printOperationRunDialog

instance O.OverloadedMethodInfo PrintOperationRunDialogMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation.printOperationRunDialog",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#v:printOperationRunDialog"
        })


#endif

-- method PrintOperation::set_page_setup
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "print_operation"
--           , argType =
--               TInterface Name { namespace = "WebKit2" , name = "PrintOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitPrintOperation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "page_setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_print_operation_set_page_setup" webkit_print_operation_set_page_setup :: 
    Ptr PrintOperation ->                   -- print_operation : TInterface (Name {namespace = "WebKit2", name = "PrintOperation"})
    Ptr Gtk.PageSetup.PageSetup ->          -- page_setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    IO ()

-- | Set the current page setup of /@printOperation@/.
-- 
-- Current page setup is used for the
-- initial values of the print dialog when 'GI.WebKit2.Objects.PrintOperation.printOperationRunDialog' is called.
printOperationSetPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a, Gtk.PageSetup.IsPageSetup b) =>
    a
    -- ^ /@printOperation@/: a t'GI.WebKit2.Objects.PrintOperation.PrintOperation'
    -> b
    -- ^ /@pageSetup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup' to set
    -> m ()
printOperationSetPageSetup :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintOperation a, IsPageSetup b) =>
a -> b -> m ()
printOperationSetPageSetup a
printOperation 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 PrintOperation
printOperation' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printOperation
    Ptr PageSetup
pageSetup' <- b -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
pageSetup
    Ptr PrintOperation -> Ptr PageSetup -> IO ()
webkit_print_operation_set_page_setup Ptr PrintOperation
printOperation' Ptr PageSetup
pageSetup'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
printOperation
    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 PrintOperationSetPageSetupMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPrintOperation a, Gtk.PageSetup.IsPageSetup b) => O.OverloadedMethod PrintOperationSetPageSetupMethodInfo a signature where
    overloadedMethod = printOperationSetPageSetup

instance O.OverloadedMethodInfo PrintOperationSetPageSetupMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation.printOperationSetPageSetup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#v:printOperationSetPageSetup"
        })


#endif

-- method PrintOperation::set_print_settings
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "print_operation"
--           , argType =
--               TInterface Name { namespace = "WebKit2" , name = "PrintOperation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #WebKitPrintOperation"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "print_settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings to set"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "webkit_print_operation_set_print_settings" webkit_print_operation_set_print_settings :: 
    Ptr PrintOperation ->                   -- print_operation : TInterface (Name {namespace = "WebKit2", name = "PrintOperation"})
    Ptr Gtk.PrintSettings.PrintSettings ->  -- print_settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO ()

-- | Set the current print settings of /@printOperation@/.
-- 
-- Set the current print settings of /@printOperation@/. Current print settings are used for
-- the initial values of the print dialog when 'GI.WebKit2.Objects.PrintOperation.printOperationRunDialog' is called.
printOperationSetPrintSettings ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a, Gtk.PrintSettings.IsPrintSettings b) =>
    a
    -- ^ /@printOperation@/: a t'GI.WebKit2.Objects.PrintOperation.PrintOperation'
    -> b
    -- ^ /@printSettings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings' to set
    -> m ()
printOperationSetPrintSettings :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrintOperation a, IsPrintSettings b) =>
a -> b -> m ()
printOperationSetPrintSettings a
printOperation 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 PrintOperation
printOperation' <- a -> IO (Ptr PrintOperation)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printOperation
    Ptr PrintSettings
printSettings' <- b -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
printSettings
    Ptr PrintOperation -> Ptr PrintSettings -> IO ()
webkit_print_operation_set_print_settings Ptr PrintOperation
printOperation' Ptr PrintSettings
printSettings'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
printOperation
    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 PrintOperationSetPrintSettingsMethodInfo
instance (signature ~ (b -> m ()), MonadIO m, IsPrintOperation a, Gtk.PrintSettings.IsPrintSettings b) => O.OverloadedMethod PrintOperationSetPrintSettingsMethodInfo a signature where
    overloadedMethod = printOperationSetPrintSettings

instance O.OverloadedMethodInfo PrintOperationSetPrintSettingsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.WebKit2.Objects.PrintOperation.printOperationSetPrintSettings",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit2-4.0.29/docs/GI-WebKit2-Objects-PrintOperation.html#v:printOperationSetPrintSettings"
        })


#endif