{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.WebKit.Objects.PrintOperation
(
PrintOperation(..) ,
IsPrintOperation ,
toPrintOperation ,
#if defined(ENABLE_OVERLOADING)
ResolvePrintOperationMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PrintOperationGetPageSetupMethodInfo ,
#endif
printOperationGetPageSetup ,
#if defined(ENABLE_OVERLOADING)
PrintOperationGetPrintSettingsMethodInfo,
#endif
printOperationGetPrintSettings ,
printOperationNew ,
#if defined(ENABLE_OVERLOADING)
PrintOperationPrintMethodInfo ,
#endif
printOperationPrint ,
#if defined(ENABLE_OVERLOADING)
PrintOperationRunDialogMethodInfo ,
#endif
printOperationRunDialog ,
#if defined(ENABLE_OVERLOADING)
PrintOperationSetPageSetupMethodInfo ,
#endif
printOperationSetPageSetup ,
#if defined(ENABLE_OVERLOADING)
PrintOperationSetPrintSettingsMethodInfo,
#endif
printOperationSetPrintSettings ,
#if defined(ENABLE_OVERLOADING)
PrintOperationPageSetupPropertyInfo ,
#endif
constructPrintOperationPageSetup ,
getPrintOperationPageSetup ,
#if defined(ENABLE_OVERLOADING)
printOperationPageSetup ,
#endif
setPrintOperationPageSetup ,
#if defined(ENABLE_OVERLOADING)
PrintOperationPrintSettingsPropertyInfo ,
#endif
constructPrintOperationPrintSettings ,
getPrintOperationPrintSettings ,
#if defined(ENABLE_OVERLOADING)
printOperationPrintSettings ,
#endif
setPrintOperationPrintSettings ,
#if defined(ENABLE_OVERLOADING)
PrintOperationWebViewPropertyInfo ,
#endif
constructPrintOperationWebView ,
getPrintOperationWebView ,
#if defined(ENABLE_OVERLOADING)
printOperationWebView ,
#endif
PrintOperationFailedCallback ,
#if defined(ENABLE_OVERLOADING)
PrintOperationFailedSignalInfo ,
#endif
afterPrintOperationFailed ,
onPrintOperationFailed ,
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.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.DateTime as GLib.DateTime
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Objects.Event as Gdk.Event
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.Action as Gio.Action
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.InputStream as Gio.InputStream
import qualified GI.Gio.Objects.TlsCertificate as Gio.TlsCertificate
import qualified GI.Gio.Objects.UnixFDList as Gio.UnixFDList
import qualified GI.Gtk.Interfaces.Accessible as Gtk.Accessible
import qualified GI.Gtk.Interfaces.Buildable as Gtk.Buildable
import qualified GI.Gtk.Interfaces.ConstraintTarget as Gtk.ConstraintTarget
import qualified GI.Gtk.Objects.FileFilter as Gtk.FileFilter
import qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings
import qualified GI.Gtk.Objects.Widget as Gtk.Widget
import qualified GI.Gtk.Objects.Window as Gtk.Window
import qualified GI.JavaScriptCore.Objects.Value as JavaScriptCore.Value
import qualified GI.Soup.Structs.Cookie as Soup.Cookie
import qualified GI.Soup.Structs.MessageHeaders as Soup.MessageHeaders
import qualified GI.WebKit.Callbacks as WebKit.Callbacks
import {-# SOURCE #-} qualified GI.WebKit.Enums as WebKit.Enums
import {-# SOURCE #-} qualified GI.WebKit.Flags as WebKit.Flags
import {-# SOURCE #-} qualified GI.WebKit.Interfaces.PermissionRequest as WebKit.PermissionRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.AuthenticationRequest as WebKit.AuthenticationRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.AutomationSession as WebKit.AutomationSession
import {-# SOURCE #-} qualified GI.WebKit.Objects.BackForwardList as WebKit.BackForwardList
import {-# SOURCE #-} qualified GI.WebKit.Objects.BackForwardListItem as WebKit.BackForwardListItem
import {-# SOURCE #-} qualified GI.WebKit.Objects.ColorChooserRequest as WebKit.ColorChooserRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.ContextMenu as WebKit.ContextMenu
import {-# SOURCE #-} qualified GI.WebKit.Objects.ContextMenuItem as WebKit.ContextMenuItem
import {-# SOURCE #-} qualified GI.WebKit.Objects.CookieManager as WebKit.CookieManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.Download as WebKit.Download
import {-# SOURCE #-} qualified GI.WebKit.Objects.EditorState as WebKit.EditorState
import {-# SOURCE #-} qualified GI.WebKit.Objects.FaviconDatabase as WebKit.FaviconDatabase
import {-# SOURCE #-} qualified GI.WebKit.Objects.FileChooserRequest as WebKit.FileChooserRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.FindController as WebKit.FindController
import {-# SOURCE #-} qualified GI.WebKit.Objects.FormSubmissionRequest as WebKit.FormSubmissionRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.GeolocationManager as WebKit.GeolocationManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.HitTestResult as WebKit.HitTestResult
import {-# SOURCE #-} qualified GI.WebKit.Objects.InputMethodContext as WebKit.InputMethodContext
import {-# SOURCE #-} qualified GI.WebKit.Objects.NetworkSession as WebKit.NetworkSession
import {-# SOURCE #-} qualified GI.WebKit.Objects.Notification as WebKit.Notification
import {-# SOURCE #-} qualified GI.WebKit.Objects.OptionMenu as WebKit.OptionMenu
import {-# SOURCE #-} qualified GI.WebKit.Objects.PolicyDecision as WebKit.PolicyDecision
import {-# SOURCE #-} qualified GI.WebKit.Objects.SecurityManager as WebKit.SecurityManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.Settings as WebKit.Settings
import {-# SOURCE #-} qualified GI.WebKit.Objects.URIRequest as WebKit.URIRequest
import {-# SOURCE #-} qualified GI.WebKit.Objects.URIResponse as WebKit.URIResponse
import {-# SOURCE #-} qualified GI.WebKit.Objects.UserContentManager as WebKit.UserContentManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.UserMessage as WebKit.UserMessage
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebContext as WebKit.WebContext
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebInspector as WebKit.WebInspector
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebResource as WebKit.WebResource
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebView as WebKit.WebView
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebViewBase as WebKit.WebViewBase
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebsiteDataManager as WebKit.WebsiteDataManager
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebsitePolicies as WebKit.WebsitePolicies
import {-# SOURCE #-} qualified GI.WebKit.Objects.WindowProperties as WebKit.WindowProperties
import {-# SOURCE #-} qualified GI.WebKit.Structs.ApplicationInfo as WebKit.ApplicationInfo
import {-# SOURCE #-} qualified GI.WebKit.Structs.Credential as WebKit.Credential
import {-# SOURCE #-} qualified GI.WebKit.Structs.Feature as WebKit.Feature
import {-# SOURCE #-} qualified GI.WebKit.Structs.FeatureList as WebKit.FeatureList
import {-# SOURCE #-} qualified GI.WebKit.Structs.GeolocationPosition as WebKit.GeolocationPosition
import {-# SOURCE #-} qualified GI.WebKit.Structs.ITPFirstParty as WebKit.ITPFirstParty
import {-# SOURCE #-} qualified GI.WebKit.Structs.ITPThirdParty as WebKit.ITPThirdParty
import {-# SOURCE #-} qualified GI.WebKit.Structs.InputMethodUnderline as WebKit.InputMethodUnderline
import {-# SOURCE #-} qualified GI.WebKit.Structs.MemoryPressureSettings as WebKit.MemoryPressureSettings
import {-# SOURCE #-} qualified GI.WebKit.Structs.NavigationAction as WebKit.NavigationAction
import {-# SOURCE #-} qualified GI.WebKit.Structs.NetworkProxySettings as WebKit.NetworkProxySettings
import {-# SOURCE #-} qualified GI.WebKit.Structs.OptionMenuItem as WebKit.OptionMenuItem
import {-# SOURCE #-} qualified GI.WebKit.Structs.PermissionStateQuery as WebKit.PermissionStateQuery
import {-# SOURCE #-} qualified GI.WebKit.Structs.ScriptDialog as WebKit.ScriptDialog
import {-# SOURCE #-} qualified GI.WebKit.Structs.ScriptMessageReply as WebKit.ScriptMessageReply
import {-# SOURCE #-} qualified GI.WebKit.Structs.SecurityOrigin as WebKit.SecurityOrigin
import {-# SOURCE #-} qualified GI.WebKit.Structs.UserContentFilter as WebKit.UserContentFilter
import {-# SOURCE #-} qualified GI.WebKit.Structs.UserScript as WebKit.UserScript
import {-# SOURCE #-} qualified GI.WebKit.Structs.UserStyleSheet as WebKit.UserStyleSheet
import {-# SOURCE #-} qualified GI.WebKit.Structs.WebViewSessionState as WebKit.WebViewSessionState
import {-# SOURCE #-} qualified GI.WebKit.Structs.WebsiteData as WebKit.WebsiteData
#else
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.WebKit.Enums as WebKit.Enums
import {-# SOURCE #-} qualified GI.WebKit.Objects.WebView as WebKit.WebView
#endif
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
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]
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
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 :: DK.Type) :: DK.Type 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
type PrintOperationFailedCallback =
GError
-> IO ()
type C_PrintOperationFailedCallback =
Ptr PrintOperation ->
Ptr GError ->
Ptr () ->
IO ()
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 o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject 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_'
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
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.WebKit.Objects.PrintOperation::failed"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#g:signal:failed"})
#endif
type PrintOperationFinishedCallback =
IO ()
type C_PrintOperationFinishedCallback =
Ptr PrintOperation ->
Ptr () ->
IO ()
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 o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject 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)
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
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.WebKit.Objects.PrintOperation::finished"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#g:signal:finished"})
#endif
getPrintOperationPageSetup :: (MonadIO m, IsPrintOperation o) => o -> m Gtk.PageSetup.PageSetup
getPrintOperationPageSetup :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m PageSetup
getPrintOperationPageSetup 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
"getPrintOperationPageSetup" (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
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)
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 = 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.WebKit.Objects.PrintOperation.pageSetup"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#g:attr:pageSetup"
})
#endif
getPrintOperationPrintSettings :: (MonadIO m, IsPrintOperation o) => o -> m Gtk.PrintSettings.PrintSettings
getPrintOperationPrintSettings :: forall (m :: * -> *) o.
(MonadIO m, IsPrintOperation o) =>
o -> m PrintSettings
getPrintOperationPrintSettings o
obj = IO PrintSettings -> m PrintSettings
forall 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
"getPrintOperationPrintSettings" (IO (Maybe PrintSettings) -> IO PrintSettings)
-> IO (Maybe PrintSettings) -> IO PrintSettings
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr PrintSettings -> PrintSettings)
-> IO (Maybe PrintSettings)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"print-settings" ManagedPtr PrintSettings -> PrintSettings
Gtk.PrintSettings.PrintSettings
setPrintOperationPrintSettings :: (MonadIO m, IsPrintOperation o, Gtk.PrintSettings.IsPrintSettings a) => o -> a -> m ()
setPrintOperationPrintSettings :: forall (m :: * -> *) o a.
(MonadIO m, IsPrintOperation o, IsPrintSettings a) =>
o -> a -> m ()
setPrintOperationPrintSettings o
obj a
val = IO () -> m ()
forall 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)
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 = 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.WebKit.Objects.PrintOperation.printSettings"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#g:attr:printSettings"
})
#endif
getPrintOperationWebView :: (MonadIO m, IsPrintOperation o) => o -> m (Maybe WebKit.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
WebKit.WebView.WebView
constructPrintOperationWebView :: (IsPrintOperation o, MIO.MonadIO m, WebKit.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 = WebKit.WebView.IsWebView
type AttrTransferTypeConstraint PrintOperationWebViewPropertyInfo = WebKit.WebView.IsWebView
type AttrTransferType PrintOperationWebViewPropertyInfo = WebKit.WebView.WebView
type AttrGetType PrintOperationWebViewPropertyInfo = (Maybe WebKit.WebView.WebView)
type AttrLabel PrintOperationWebViewPropertyInfo = "web-view"
type AttrOrigin PrintOperationWebViewPropertyInfo = PrintOperation
attrGet = getPrintOperationWebView
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo WebKit.WebView.WebView v
attrConstruct = constructPrintOperationWebView
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.PrintOperation.webView"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-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, DK.Type)])
#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 = ('[ '("failed", PrintOperationFailedSignalInfo), '("finished", PrintOperationFinishedSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "webkit_print_operation_new" webkit_print_operation_new ::
Ptr WebKit.WebView.WebView ->
IO (Ptr PrintOperation)
printOperationNew ::
(B.CallStack.HasCallStack, MonadIO m, WebKit.WebView.IsWebView a) =>
a
-> m 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
foreign import ccall "webkit_print_operation_get_page_setup" webkit_print_operation_get_page_setup ::
Ptr PrintOperation ->
IO (Ptr Gtk.PageSetup.PageSetup)
printOperationGetPageSetup ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
a
-> m Gtk.PageSetup.PageSetup
printOperationGetPageSetup :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m PageSetup
printOperationGetPageSetup a
printOperation = 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 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'
Text -> Ptr PageSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printOperationGetPageSetup" 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
printOperation
PageSetup -> IO PageSetup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetPageSetupMethodInfo
instance (signature ~ (m 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.WebKit.Objects.PrintOperation.printOperationGetPageSetup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#v:printOperationGetPageSetup"
})
#endif
foreign import ccall "webkit_print_operation_get_print_settings" webkit_print_operation_get_print_settings ::
Ptr PrintOperation ->
IO (Ptr Gtk.PrintSettings.PrintSettings)
printOperationGetPrintSettings ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
a
-> m Gtk.PrintSettings.PrintSettings
printOperationGetPrintSettings :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperation a) =>
a -> m PrintSettings
printOperationGetPrintSettings a
printOperation = 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 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'
Text -> Ptr PrintSettings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printOperationGetPrintSettings" Ptr PrintSettings
result
PrintSettings
result' <- ((ManagedPtr PrintSettings -> PrintSettings)
-> Ptr PrintSettings -> IO PrintSettings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintSettings -> PrintSettings
Gtk.PrintSettings.PrintSettings) Ptr PrintSettings
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
printOperation
PrintSettings -> IO PrintSettings
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result'
#if defined(ENABLE_OVERLOADING)
data PrintOperationGetPrintSettingsMethodInfo
instance (signature ~ (m Gtk.PrintSettings.PrintSettings), MonadIO m, IsPrintOperation a) => O.OverloadedMethod PrintOperationGetPrintSettingsMethodInfo a signature where
overloadedMethod = printOperationGetPrintSettings
instance O.OverloadedMethodInfo PrintOperationGetPrintSettingsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.WebKit.Objects.PrintOperation.printOperationGetPrintSettings",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#v:printOperationGetPrintSettings"
})
#endif
foreign import ccall "webkit_print_operation_print" webkit_print_operation_print ::
Ptr PrintOperation ->
IO ()
printOperationPrint ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a) =>
a
-> 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.WebKit.Objects.PrintOperation.printOperationPrint",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#v:printOperationPrint"
})
#endif
foreign import ccall "webkit_print_operation_run_dialog" webkit_print_operation_run_dialog ::
Ptr PrintOperation ->
Ptr Gtk.Window.Window ->
IO CUInt
printOperationRunDialog ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a, Gtk.Window.IsWindow b) =>
a
-> Maybe (b)
-> m WebKit.Enums.PrintOperationResponse
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 WebKit.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.WebKit.Objects.PrintOperation.printOperationRunDialog",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#v:printOperationRunDialog"
})
#endif
foreign import ccall "webkit_print_operation_set_page_setup" webkit_print_operation_set_page_setup ::
Ptr PrintOperation ->
Ptr Gtk.PageSetup.PageSetup ->
IO ()
printOperationSetPageSetup ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a, Gtk.PageSetup.IsPageSetup b) =>
a
-> b
-> 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.WebKit.Objects.PrintOperation.printOperationSetPageSetup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#v:printOperationSetPageSetup"
})
#endif
foreign import ccall "webkit_print_operation_set_print_settings" webkit_print_operation_set_print_settings ::
Ptr PrintOperation ->
Ptr Gtk.PrintSettings.PrintSettings ->
IO ()
printOperationSetPrintSettings ::
(B.CallStack.HasCallStack, MonadIO m, IsPrintOperation a, Gtk.PrintSettings.IsPrintSettings b) =>
a
-> b
-> 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.WebKit.Objects.PrintOperation.printOperationSetPrintSettings",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-webkit-6.0.3/docs/GI-WebKit-Objects-PrintOperation.html#v:printOperationSetPrintSettings"
})
#endif