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


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GtkPrintOperationPreview@ is the interface that is used to
-- implement print preview.
-- 
-- A @GtkPrintOperationPreview@ object is passed to the
-- [PrintOperation::preview]("GI.Gtk.Objects.PrintOperation#g:signal:preview") signal by
-- t'GI.Gtk.Objects.PrintOperation.PrintOperation'.

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

module GI.Gtk.Interfaces.PrintOperationPreview
    ( 

-- * Exported types
    PrintOperationPreview(..)               ,
    IsPrintOperationPreview                 ,
    toPrintOperationPreview                 ,


 -- * 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"), [endPreview]("GI.Gtk.Interfaces.PrintOperationPreview#g:method:endPreview"), [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"), [isSelected]("GI.Gtk.Interfaces.PrintOperationPreview#g:method:isSelected"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [renderPage]("GI.Gtk.Interfaces.PrintOperationPreview#g:method:renderPage"), [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"), [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"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolvePrintOperationPreviewMethod      ,
#endif

-- ** endPreview #method:endPreview#

#if defined(ENABLE_OVERLOADING)
    PrintOperationPreviewEndPreviewMethodInfo,
#endif
    printOperationPreviewEndPreview         ,


-- ** isSelected #method:isSelected#

#if defined(ENABLE_OVERLOADING)
    PrintOperationPreviewIsSelectedMethodInfo,
#endif
    printOperationPreviewIsSelected         ,


-- ** renderPage #method:renderPage#

#if defined(ENABLE_OVERLOADING)
    PrintOperationPreviewRenderPageMethodInfo,
#endif
    printOperationPreviewRenderPage         ,




 -- * Signals


-- ** gotPageSize #signal:gotPageSize#

    PrintOperationPreviewGotPageSizeCallback,
#if defined(ENABLE_OVERLOADING)
    PrintOperationPreviewGotPageSizeSignalInfo,
#endif
    afterPrintOperationPreviewGotPageSize   ,
    onPrintOperationPreviewGotPageSize      ,


-- ** ready #signal:ready#

    PrintOperationPreviewReadyCallback      ,
#if defined(ENABLE_OVERLOADING)
    PrintOperationPreviewReadySignalInfo    ,
#endif
    afterPrintOperationPreviewReady         ,
    onPrintOperationPreviewReady            ,




    ) where

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

import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.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 {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Objects.PrintContext as Gtk.PrintContext

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

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

foreign import ccall "gtk_print_operation_preview_get_type"
    c_gtk_print_operation_preview_get_type :: IO B.Types.GType

instance B.Types.TypedObject PrintOperationPreview where
    glibType :: IO GType
glibType = IO GType
c_gtk_print_operation_preview_get_type

instance B.Types.GObject PrintOperationPreview

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

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

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

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

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PrintOperationPreview
type instance O.AttributeList PrintOperationPreview = PrintOperationPreviewAttributeList
type PrintOperationPreviewAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type family ResolvePrintOperationPreviewMethod (t :: Symbol) (o :: *) :: * where
    ResolvePrintOperationPreviewMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePrintOperationPreviewMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePrintOperationPreviewMethod "endPreview" o = PrintOperationPreviewEndPreviewMethodInfo
    ResolvePrintOperationPreviewMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePrintOperationPreviewMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePrintOperationPreviewMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePrintOperationPreviewMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePrintOperationPreviewMethod "isSelected" o = PrintOperationPreviewIsSelectedMethodInfo
    ResolvePrintOperationPreviewMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePrintOperationPreviewMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePrintOperationPreviewMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePrintOperationPreviewMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePrintOperationPreviewMethod "renderPage" o = PrintOperationPreviewRenderPageMethodInfo
    ResolvePrintOperationPreviewMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePrintOperationPreviewMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePrintOperationPreviewMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePrintOperationPreviewMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePrintOperationPreviewMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePrintOperationPreviewMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePrintOperationPreviewMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePrintOperationPreviewMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePrintOperationPreviewMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePrintOperationPreviewMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePrintOperationPreviewMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePrintOperationPreviewMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePrintOperationPreviewMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif

-- method PrintOperationPreview::end_preview
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "preview"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "PrintOperationPreview" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintOperationPreview`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_operation_preview_end_preview" gtk_print_operation_preview_end_preview :: 
    Ptr PrintOperationPreview ->            -- preview : TInterface (Name {namespace = "Gtk", name = "PrintOperationPreview"})
    IO ()

-- | Ends a preview.
-- 
-- This function must be called to finish a custom print preview.
printOperationPreviewEndPreview ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperationPreview a) =>
    a
    -- ^ /@preview@/: a @GtkPrintOperationPreview@
    -> m ()
printOperationPreviewEndPreview :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperationPreview a) =>
a -> m ()
printOperationPreviewEndPreview a
preview = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperationPreview
preview' <- a -> IO (Ptr PrintOperationPreview)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
preview
    Ptr PrintOperationPreview -> IO ()
gtk_print_operation_preview_end_preview Ptr PrintOperationPreview
preview'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
preview
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintOperationPreviewEndPreviewMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPrintOperationPreview a) => O.OverloadedMethod PrintOperationPreviewEndPreviewMethodInfo a signature where
    overloadedMethod = printOperationPreviewEndPreview

instance O.OverloadedMethodInfo PrintOperationPreviewEndPreviewMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.PrintOperationPreview.printOperationPreviewEndPreview",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-PrintOperationPreview.html#v:printOperationPreviewEndPreview"
        })


#endif

-- method PrintOperationPreview::is_selected
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "preview"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "PrintOperationPreview" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintOperationPreview`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "page_nr"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a page number" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_operation_preview_is_selected" gtk_print_operation_preview_is_selected :: 
    Ptr PrintOperationPreview ->            -- preview : TInterface (Name {namespace = "Gtk", name = "PrintOperationPreview"})
    Int32 ->                                -- page_nr : TBasicType TInt
    IO CInt

-- | Returns whether the given page is included in the set of pages that
-- have been selected for printing.
printOperationPreviewIsSelected ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperationPreview a) =>
    a
    -- ^ /@preview@/: a @GtkPrintOperationPreview@
    -> Int32
    -- ^ /@pageNr@/: a page number
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the page has been selected for printing
printOperationPreviewIsSelected :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperationPreview a) =>
a -> Int32 -> m Bool
printOperationPreviewIsSelected a
preview Int32
pageNr = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperationPreview
preview' <- a -> IO (Ptr PrintOperationPreview)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
preview
    CInt
result <- Ptr PrintOperationPreview -> Int32 -> IO CInt
gtk_print_operation_preview_is_selected Ptr PrintOperationPreview
preview' Int32
pageNr
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
preview
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PrintOperationPreviewIsSelectedMethodInfo
instance (signature ~ (Int32 -> m Bool), MonadIO m, IsPrintOperationPreview a) => O.OverloadedMethod PrintOperationPreviewIsSelectedMethodInfo a signature where
    overloadedMethod = printOperationPreviewIsSelected

instance O.OverloadedMethodInfo PrintOperationPreviewIsSelectedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.PrintOperationPreview.printOperationPreviewIsSelected",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-PrintOperationPreview.html#v:printOperationPreviewIsSelected"
        })


#endif

-- method PrintOperationPreview::render_page
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "preview"
--           , argType =
--               TInterface
--                 Name { namespace = "Gtk" , name = "PrintOperationPreview" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GtkPrintOperationPreview`"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "page_nr"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the page to render" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_operation_preview_render_page" gtk_print_operation_preview_render_page :: 
    Ptr PrintOperationPreview ->            -- preview : TInterface (Name {namespace = "Gtk", name = "PrintOperationPreview"})
    Int32 ->                                -- page_nr : TBasicType TInt
    IO ()

-- | Renders a page to the preview.
-- 
-- This is using the print context that was passed to the
-- [PrintOperation::preview]("GI.Gtk.Objects.PrintOperation#g:signal:preview") handler together
-- with /@preview@/.
-- 
-- A custom print preview should use this function to render
-- the currently selected page.
-- 
-- Note that this function requires a suitable cairo context to
-- be associated with the print context.
printOperationPreviewRenderPage ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintOperationPreview a) =>
    a
    -- ^ /@preview@/: a @GtkPrintOperationPreview@
    -> Int32
    -- ^ /@pageNr@/: the page to render
    -> m ()
printOperationPreviewRenderPage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrintOperationPreview a) =>
a -> Int32 -> m ()
printOperationPreviewRenderPage a
preview Int32
pageNr = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintOperationPreview
preview' <- a -> IO (Ptr PrintOperationPreview)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
preview
    Ptr PrintOperationPreview -> Int32 -> IO ()
gtk_print_operation_preview_render_page Ptr PrintOperationPreview
preview' Int32
pageNr
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
preview
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintOperationPreviewRenderPageMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsPrintOperationPreview a) => O.OverloadedMethod PrintOperationPreviewRenderPageMethodInfo a signature where
    overloadedMethod = printOperationPreviewRenderPage

instance O.OverloadedMethodInfo PrintOperationPreviewRenderPageMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.PrintOperationPreview.printOperationPreviewRenderPage",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-PrintOperationPreview.html#v:printOperationPreviewRenderPage"
        })


#endif

-- signal PrintOperationPreview::got-page-size
-- | Emitted once for each page that gets rendered to the preview.
-- 
-- A handler for this signal should update the /@context@/
-- according to /@pageSetup@/ and set up a suitable cairo
-- context, using 'GI.Gtk.Objects.PrintContext.printContextSetCairoContext'.
type PrintOperationPreviewGotPageSizeCallback =
    Gtk.PrintContext.PrintContext
    -- ^ /@context@/: the current @GtkPrintContext@
    -> Gtk.PageSetup.PageSetup
    -- ^ /@pageSetup@/: the @GtkPageSetup@ for the current page
    -> IO ()

type C_PrintOperationPreviewGotPageSizeCallback =
    Ptr PrintOperationPreview ->            -- object
    Ptr Gtk.PrintContext.PrintContext ->
    Ptr Gtk.PageSetup.PageSetup ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_PrintOperationPreviewGotPageSizeCallback :: 
    GObject a => (a -> PrintOperationPreviewGotPageSizeCallback) ->
    C_PrintOperationPreviewGotPageSizeCallback
wrap_PrintOperationPreviewGotPageSizeCallback :: forall a.
GObject a =>
(a -> PrintOperationPreviewGotPageSizeCallback)
-> C_PrintOperationPreviewGotPageSizeCallback
wrap_PrintOperationPreviewGotPageSizeCallback a -> PrintOperationPreviewGotPageSizeCallback
gi'cb Ptr PrintOperationPreview
gi'selfPtr Ptr PrintContext
context Ptr PageSetup
pageSetup Ptr ()
_ = do
    PrintContext
context' <- ((ManagedPtr PrintContext -> PrintContext)
-> Ptr PrintContext -> IO PrintContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintContext -> PrintContext
Gtk.PrintContext.PrintContext) Ptr PrintContext
context
    PageSetup
pageSetup' <- ((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
pageSetup
    Ptr PrintOperationPreview
-> (PrintOperationPreview -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr PrintOperationPreview
gi'selfPtr ((PrintOperationPreview -> IO ()) -> IO ())
-> (PrintOperationPreview -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \PrintOperationPreview
gi'self -> a -> PrintOperationPreviewGotPageSizeCallback
gi'cb (PrintOperationPreview -> a
Coerce.coerce PrintOperationPreview
gi'self)  PrintContext
context' PageSetup
pageSetup'


-- | Connect a signal handler for the [gotPageSize](#signal:gotPageSize) 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' printOperationPreview #gotPageSize callback
-- @
-- 
-- 
onPrintOperationPreviewGotPageSize :: (IsPrintOperationPreview a, MonadIO m) => a -> ((?self :: a) => PrintOperationPreviewGotPageSizeCallback) -> m SignalHandlerId
onPrintOperationPreviewGotPageSize :: forall a (m :: * -> *).
(IsPrintOperationPreview a, MonadIO m) =>
a
-> ((?self::a) => PrintOperationPreviewGotPageSizeCallback)
-> m SignalHandlerId
onPrintOperationPreviewGotPageSize a
obj (?self::a) => PrintOperationPreviewGotPageSizeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PrintOperationPreviewGotPageSizeCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PrintOperationPreviewGotPageSizeCallback
PrintOperationPreviewGotPageSizeCallback
cb
    let wrapped' :: C_PrintOperationPreviewGotPageSizeCallback
wrapped' = (a -> PrintOperationPreviewGotPageSizeCallback)
-> C_PrintOperationPreviewGotPageSizeCallback
forall a.
GObject a =>
(a -> PrintOperationPreviewGotPageSizeCallback)
-> C_PrintOperationPreviewGotPageSizeCallback
wrap_PrintOperationPreviewGotPageSizeCallback a -> PrintOperationPreviewGotPageSizeCallback
wrapped
    FunPtr C_PrintOperationPreviewGotPageSizeCallback
wrapped'' <- C_PrintOperationPreviewGotPageSizeCallback
-> IO (FunPtr C_PrintOperationPreviewGotPageSizeCallback)
mk_PrintOperationPreviewGotPageSizeCallback C_PrintOperationPreviewGotPageSizeCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationPreviewGotPageSizeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"got-page-size" FunPtr C_PrintOperationPreviewGotPageSizeCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [gotPageSize](#signal:gotPageSize) 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' printOperationPreview #gotPageSize 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.
-- 
afterPrintOperationPreviewGotPageSize :: (IsPrintOperationPreview a, MonadIO m) => a -> ((?self :: a) => PrintOperationPreviewGotPageSizeCallback) -> m SignalHandlerId
afterPrintOperationPreviewGotPageSize :: forall a (m :: * -> *).
(IsPrintOperationPreview a, MonadIO m) =>
a
-> ((?self::a) => PrintOperationPreviewGotPageSizeCallback)
-> m SignalHandlerId
afterPrintOperationPreviewGotPageSize a
obj (?self::a) => PrintOperationPreviewGotPageSizeCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PrintOperationPreviewGotPageSizeCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PrintOperationPreviewGotPageSizeCallback
PrintOperationPreviewGotPageSizeCallback
cb
    let wrapped' :: C_PrintOperationPreviewGotPageSizeCallback
wrapped' = (a -> PrintOperationPreviewGotPageSizeCallback)
-> C_PrintOperationPreviewGotPageSizeCallback
forall a.
GObject a =>
(a -> PrintOperationPreviewGotPageSizeCallback)
-> C_PrintOperationPreviewGotPageSizeCallback
wrap_PrintOperationPreviewGotPageSizeCallback a -> PrintOperationPreviewGotPageSizeCallback
wrapped
    FunPtr C_PrintOperationPreviewGotPageSizeCallback
wrapped'' <- C_PrintOperationPreviewGotPageSizeCallback
-> IO (FunPtr C_PrintOperationPreviewGotPageSizeCallback)
mk_PrintOperationPreviewGotPageSizeCallback C_PrintOperationPreviewGotPageSizeCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationPreviewGotPageSizeCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"got-page-size" FunPtr C_PrintOperationPreviewGotPageSizeCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PrintOperationPreviewGotPageSizeSignalInfo
instance SignalInfo PrintOperationPreviewGotPageSizeSignalInfo where
    type HaskellCallbackType PrintOperationPreviewGotPageSizeSignalInfo = PrintOperationPreviewGotPageSizeCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationPreviewGotPageSizeCallback cb
        cb'' <- mk_PrintOperationPreviewGotPageSizeCallback cb'
        connectSignalFunPtr obj "got-page-size" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.PrintOperationPreview::got-page-size"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-PrintOperationPreview.html#g:signal:gotPageSize"})

#endif

-- signal PrintOperationPreview::ready
-- | The [ready](#g:signal:ready) signal gets emitted once per preview operation,
-- before the first page is rendered.
-- 
-- A handler for this signal can be used for setup tasks.
type PrintOperationPreviewReadyCallback =
    Gtk.PrintContext.PrintContext
    -- ^ /@context@/: the current @GtkPrintContext@
    -> IO ()

type C_PrintOperationPreviewReadyCallback =
    Ptr PrintOperationPreview ->            -- object
    Ptr Gtk.PrintContext.PrintContext ->
    Ptr () ->                               -- user_data
    IO ()

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

wrap_PrintOperationPreviewReadyCallback :: 
    GObject a => (a -> PrintOperationPreviewReadyCallback) ->
    C_PrintOperationPreviewReadyCallback
wrap_PrintOperationPreviewReadyCallback :: forall a.
GObject a =>
(a -> PrintOperationPreviewReadyCallback)
-> C_PrintOperationPreviewReadyCallback
wrap_PrintOperationPreviewReadyCallback a -> PrintOperationPreviewReadyCallback
gi'cb Ptr PrintOperationPreview
gi'selfPtr Ptr PrintContext
context Ptr ()
_ = do
    PrintContext
context' <- ((ManagedPtr PrintContext -> PrintContext)
-> Ptr PrintContext -> IO PrintContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintContext -> PrintContext
Gtk.PrintContext.PrintContext) Ptr PrintContext
context
    Ptr PrintOperationPreview
-> (PrintOperationPreview -> IO ()) -> IO ()
forall a b.
(HasCallStack, ManagedPtrNewtype a) =>
Ptr a -> (a -> IO b) -> IO b
B.ManagedPtr.withTransient Ptr PrintOperationPreview
gi'selfPtr ((PrintOperationPreview -> IO ()) -> IO ())
-> (PrintOperationPreview -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \PrintOperationPreview
gi'self -> a -> PrintOperationPreviewReadyCallback
gi'cb (PrintOperationPreview -> a
Coerce.coerce PrintOperationPreview
gi'self)  PrintContext
context'


-- | Connect a signal handler for the [ready](#signal:ready) 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' printOperationPreview #ready callback
-- @
-- 
-- 
onPrintOperationPreviewReady :: (IsPrintOperationPreview a, MonadIO m) => a -> ((?self :: a) => PrintOperationPreviewReadyCallback) -> m SignalHandlerId
onPrintOperationPreviewReady :: forall a (m :: * -> *).
(IsPrintOperationPreview a, MonadIO m) =>
a
-> ((?self::a) => PrintOperationPreviewReadyCallback)
-> m SignalHandlerId
onPrintOperationPreviewReady a
obj (?self::a) => PrintOperationPreviewReadyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PrintOperationPreviewReadyCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PrintOperationPreviewReadyCallback
PrintOperationPreviewReadyCallback
cb
    let wrapped' :: C_PrintOperationPreviewReadyCallback
wrapped' = (a -> PrintOperationPreviewReadyCallback)
-> C_PrintOperationPreviewReadyCallback
forall a.
GObject a =>
(a -> PrintOperationPreviewReadyCallback)
-> C_PrintOperationPreviewReadyCallback
wrap_PrintOperationPreviewReadyCallback a -> PrintOperationPreviewReadyCallback
wrapped
    FunPtr C_PrintOperationPreviewReadyCallback
wrapped'' <- C_PrintOperationPreviewReadyCallback
-> IO (FunPtr C_PrintOperationPreviewReadyCallback)
mk_PrintOperationPreviewReadyCallback C_PrintOperationPreviewReadyCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationPreviewReadyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"ready" FunPtr C_PrintOperationPreviewReadyCallback
wrapped'' SignalConnectMode
SignalConnectBefore Maybe Text
forall a. Maybe a
Nothing

-- | Connect a signal handler for the [ready](#signal:ready) 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' printOperationPreview #ready 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.
-- 
afterPrintOperationPreviewReady :: (IsPrintOperationPreview a, MonadIO m) => a -> ((?self :: a) => PrintOperationPreviewReadyCallback) -> m SignalHandlerId
afterPrintOperationPreviewReady :: forall a (m :: * -> *).
(IsPrintOperationPreview a, MonadIO m) =>
a
-> ((?self::a) => PrintOperationPreviewReadyCallback)
-> m SignalHandlerId
afterPrintOperationPreviewReady a
obj (?self::a) => PrintOperationPreviewReadyCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
    let wrapped :: a -> PrintOperationPreviewReadyCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PrintOperationPreviewReadyCallback
PrintOperationPreviewReadyCallback
cb
    let wrapped' :: C_PrintOperationPreviewReadyCallback
wrapped' = (a -> PrintOperationPreviewReadyCallback)
-> C_PrintOperationPreviewReadyCallback
forall a.
GObject a =>
(a -> PrintOperationPreviewReadyCallback)
-> C_PrintOperationPreviewReadyCallback
wrap_PrintOperationPreviewReadyCallback a -> PrintOperationPreviewReadyCallback
wrapped
    FunPtr C_PrintOperationPreviewReadyCallback
wrapped'' <- C_PrintOperationPreviewReadyCallback
-> IO (FunPtr C_PrintOperationPreviewReadyCallback)
mk_PrintOperationPreviewReadyCallback C_PrintOperationPreviewReadyCallback
wrapped'
    a
-> Text
-> FunPtr C_PrintOperationPreviewReadyCallback
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
forall o a.
GObject o =>
o
-> Text
-> FunPtr a
-> SignalConnectMode
-> Maybe Text
-> IO SignalHandlerId
connectSignalFunPtr a
obj Text
"ready" FunPtr C_PrintOperationPreviewReadyCallback
wrapped'' SignalConnectMode
SignalConnectAfter Maybe Text
forall a. Maybe a
Nothing


#if defined(ENABLE_OVERLOADING)
data PrintOperationPreviewReadySignalInfo
instance SignalInfo PrintOperationPreviewReadySignalInfo where
    type HaskellCallbackType PrintOperationPreviewReadySignalInfo = PrintOperationPreviewReadyCallback
    connectSignal obj cb connectMode detail = do
        let cb' = wrap_PrintOperationPreviewReadyCallback cb
        cb'' <- mk_PrintOperationPreviewReadyCallback cb'
        connectSignalFunPtr obj "ready" cb'' connectMode detail
    dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Interfaces.PrintOperationPreview::ready"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.5/docs/GI-Gtk-Interfaces-PrintOperationPreview.html#g:signal:ready"})

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PrintOperationPreview = PrintOperationPreviewSignalList
type PrintOperationPreviewSignalList = ('[ '("gotPageSize", PrintOperationPreviewGotPageSizeSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo), '("ready", PrintOperationPreviewReadySignalInfo)] :: [(Symbol, *)])

#endif