{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A @GtkPrintSetup@ is an auxiliary object for printing that allows decoupling
-- the setup from the printing.
-- 
-- A print setup is obtained by calling 'GI.Gtk.Objects.PrintDialog.printDialogSetup',
-- and can later be passed to print functions such as 'GI.Gtk.Objects.PrintDialog.printDialogPrint'.
-- 
-- Print setups can be reused for multiple print calls.
-- 
-- Applications may wish to store the page_setup and print_settings from the print setup
-- and copy them to the PrintDialog if they want to keep using them.
-- 
-- /Since: 4.14/

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

module GI.Gtk.Structs.PrintSetup
    ( 

-- * Exported types
    PrintSetup(..)                          ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [ref]("GI.Gtk.Structs.PrintSetup#g:method:ref"), [unref]("GI.Gtk.Structs.PrintSetup#g:method:unref").
-- 
-- ==== Getters
-- [getPageSetup]("GI.Gtk.Structs.PrintSetup#g:method:getPageSetup"), [getPrintSettings]("GI.Gtk.Structs.PrintSetup#g:method:getPrintSettings").
-- 
-- ==== Setters
-- /None/.

#if defined(ENABLE_OVERLOADING)
    ResolvePrintSetupMethod                 ,
#endif

-- ** getPageSetup #method:getPageSetup#

#if defined(ENABLE_OVERLOADING)
    PrintSetupGetPageSetupMethodInfo        ,
#endif
    printSetupGetPageSetup                  ,


-- ** getPrintSettings #method:getPrintSettings#

#if defined(ENABLE_OVERLOADING)
    PrintSetupGetPrintSettingsMethodInfo    ,
#endif
    printSetupGetPrintSettings              ,


-- ** ref #method:ref#

#if defined(ENABLE_OVERLOADING)
    PrintSetupRefMethodInfo                 ,
#endif
    printSetupRef                           ,


-- ** unref #method:unref#

#if defined(ENABLE_OVERLOADING)
    PrintSetupUnrefMethodInfo               ,
#endif
    printSetupUnref                         ,




    ) where

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

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

-- Workaround for https://gitlab.haskell.org/ghc/ghc/-/issues/23392
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings
import {-# SOURCE #-} qualified GI.Gtk.Structs.PageRange as Gtk.PageRange
import {-# SOURCE #-} qualified GI.Gtk.Structs.PaperSize as Gtk.PaperSize

#else
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings

#endif

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

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

foreign import ccall "gtk_print_setup_get_type" c_gtk_print_setup_get_type :: 
    IO GType

type instance O.ParentTypes PrintSetup = '[]
instance O.HasParentTypes PrintSetup

instance B.Types.TypedObject PrintSetup where
    glibType :: IO GType
glibType = IO GType
c_gtk_print_setup_get_type

instance B.Types.GBoxed PrintSetup

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


#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PrintSetup
type instance O.AttributeList PrintSetup = PrintSetupAttributeList
type PrintSetupAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif

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

foreign import ccall "gtk_print_setup_get_page_setup" gtk_print_setup_get_page_setup :: 
    Ptr PrintSetup ->                       -- setup : TInterface (Name {namespace = "Gtk", name = "PrintSetup"})
    IO (Ptr Gtk.PageSetup.PageSetup)

-- | Returns the page setup of /@setup@/.
-- 
-- It may be different from the @GtkPrintDialog@\'s page setup
-- if the user changed it during the setup process.
-- 
-- /Since: 4.14/
printSetupGetPageSetup ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    PrintSetup
    -- ^ /@setup@/: a @GtkPrintSetup@
    -> m (Maybe Gtk.PageSetup.PageSetup)
    -- ^ __Returns:__ the page setup, or @NULL@
printSetupGetPageSetup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PrintSetup -> m (Maybe PageSetup)
printSetupGetPageSetup PrintSetup
setup = IO (Maybe PageSetup) -> m (Maybe PageSetup)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PageSetup) -> m (Maybe PageSetup))
-> IO (Maybe PageSetup) -> m (Maybe PageSetup)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSetup
setup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
setup
    Ptr PageSetup
result <- Ptr PrintSetup -> IO (Ptr PageSetup)
gtk_print_setup_get_page_setup Ptr PrintSetup
setup'
    Maybe PageSetup
maybeResult <- Ptr PageSetup
-> (Ptr PageSetup -> IO PageSetup) -> IO (Maybe PageSetup)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PageSetup
result ((Ptr PageSetup -> IO PageSetup) -> IO (Maybe PageSetup))
-> (Ptr PageSetup -> IO PageSetup) -> IO (Maybe PageSetup)
forall a b. (a -> b) -> a -> b
$ \Ptr PageSetup
result' -> do
        PageSetup
result'' <- ((ManagedPtr PageSetup -> PageSetup)
-> Ptr PageSetup -> IO PageSetup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PageSetup -> PageSetup
Gtk.PageSetup.PageSetup) Ptr PageSetup
result'
        PageSetup -> IO PageSetup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result''
    PrintSetup -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PrintSetup
setup
    Maybe PageSetup -> IO (Maybe PageSetup)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PageSetup
maybeResult

#if defined(ENABLE_OVERLOADING)
data PrintSetupGetPageSetupMethodInfo
instance (signature ~ (m (Maybe Gtk.PageSetup.PageSetup)), MonadIO m) => O.OverloadedMethod PrintSetupGetPageSetupMethodInfo PrintSetup signature where
    overloadedMethod = printSetupGetPageSetup

instance O.OverloadedMethodInfo PrintSetupGetPageSetupMethodInfo PrintSetup where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.PrintSetup.printSetupGetPageSetup",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Structs-PrintSetup.html#v:printSetupGetPageSetup"
        })


#endif

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

foreign import ccall "gtk_print_setup_get_print_settings" gtk_print_setup_get_print_settings :: 
    Ptr PrintSetup ->                       -- setup : TInterface (Name {namespace = "Gtk", name = "PrintSetup"})
    IO (Ptr Gtk.PrintSettings.PrintSettings)

-- | Returns the print settings of /@setup@/.
-- 
-- They may be different from the @GtkPrintDialog@\'s settings
-- if the user changed them during the setup process.
-- 
-- /Since: 4.14/
printSetupGetPrintSettings ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    PrintSetup
    -- ^ /@setup@/: a @GtkPrintSetup@
    -> m (Maybe Gtk.PrintSettings.PrintSettings)
    -- ^ __Returns:__ the print settings, or @NULL@
printSetupGetPrintSettings :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PrintSetup -> m (Maybe PrintSettings)
printSetupGetPrintSettings PrintSetup
setup = IO (Maybe PrintSettings) -> m (Maybe PrintSettings)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe PrintSettings) -> m (Maybe PrintSettings))
-> IO (Maybe PrintSettings) -> m (Maybe PrintSettings)
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSetup
setup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
setup
    Ptr PrintSettings
result <- Ptr PrintSetup -> IO (Ptr PrintSettings)
gtk_print_setup_get_print_settings Ptr PrintSetup
setup'
    Maybe PrintSettings
maybeResult <- Ptr PrintSettings
-> (Ptr PrintSettings -> IO PrintSettings)
-> IO (Maybe PrintSettings)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr PrintSettings
result ((Ptr PrintSettings -> IO PrintSettings)
 -> IO (Maybe PrintSettings))
-> (Ptr PrintSettings -> IO PrintSettings)
-> IO (Maybe PrintSettings)
forall a b. (a -> b) -> a -> b
$ \Ptr PrintSettings
result' -> do
        PrintSettings
result'' <- ((ManagedPtr PrintSettings -> PrintSettings)
-> Ptr PrintSettings -> IO PrintSettings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr PrintSettings -> PrintSettings
Gtk.PrintSettings.PrintSettings) Ptr PrintSettings
result'
        PrintSettings -> IO PrintSettings
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result''
    PrintSetup -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PrintSetup
setup
    Maybe PrintSettings -> IO (Maybe PrintSettings)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PrintSettings
maybeResult

#if defined(ENABLE_OVERLOADING)
data PrintSetupGetPrintSettingsMethodInfo
instance (signature ~ (m (Maybe Gtk.PrintSettings.PrintSettings)), MonadIO m) => O.OverloadedMethod PrintSetupGetPrintSettingsMethodInfo PrintSetup signature where
    overloadedMethod = printSetupGetPrintSettings

instance O.OverloadedMethodInfo PrintSetupGetPrintSettingsMethodInfo PrintSetup where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.PrintSetup.printSetupGetPrintSettings",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Structs-PrintSetup.html#v:printSetupGetPrintSettings"
        })


#endif

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

foreign import ccall "gtk_print_setup_ref" gtk_print_setup_ref :: 
    Ptr PrintSetup ->                       -- setup : TInterface (Name {namespace = "Gtk", name = "PrintSetup"})
    IO (Ptr PrintSetup)

-- | Increase the reference count of /@setup@/.
-- 
-- /Since: 4.14/
printSetupRef ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    PrintSetup
    -- ^ /@setup@/: a @GtkPrintSetup@
    -> m PrintSetup
    -- ^ __Returns:__ the print setup
printSetupRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PrintSetup -> m PrintSetup
printSetupRef PrintSetup
setup = IO PrintSetup -> m PrintSetup
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintSetup -> m PrintSetup) -> IO PrintSetup -> m PrintSetup
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSetup
setup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
setup
    Ptr PrintSetup
result <- Ptr PrintSetup -> IO (Ptr PrintSetup)
gtk_print_setup_ref Ptr PrintSetup
setup'
    Text -> Ptr PrintSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"printSetupRef" Ptr PrintSetup
result
    PrintSetup
result' <- ((ManagedPtr PrintSetup -> PrintSetup)
-> Ptr PrintSetup -> IO PrintSetup
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr PrintSetup -> PrintSetup
PrintSetup) Ptr PrintSetup
result
    PrintSetup -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PrintSetup
setup
    PrintSetup -> IO PrintSetup
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSetup
result'

#if defined(ENABLE_OVERLOADING)
data PrintSetupRefMethodInfo
instance (signature ~ (m PrintSetup), MonadIO m) => O.OverloadedMethod PrintSetupRefMethodInfo PrintSetup signature where
    overloadedMethod = printSetupRef

instance O.OverloadedMethodInfo PrintSetupRefMethodInfo PrintSetup where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.PrintSetup.printSetupRef",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Structs-PrintSetup.html#v:printSetupRef"
        })


#endif

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

foreign import ccall "gtk_print_setup_unref" gtk_print_setup_unref :: 
    Ptr PrintSetup ->                       -- setup : TInterface (Name {namespace = "Gtk", name = "PrintSetup"})
    IO ()

-- | Decrease the reference count of /@setup@/.
-- 
-- If the reference count reaches zero,
-- the object is freed.
-- 
-- /Since: 4.14/
printSetupUnref ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    PrintSetup
    -- ^ /@setup@/: a @GtkPrintSetup@
    -> m ()
printSetupUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PrintSetup -> m ()
printSetupUnref PrintSetup
setup = 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 PrintSetup
setup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
setup
    Ptr PrintSetup -> IO ()
gtk_print_setup_unref Ptr PrintSetup
setup'
    PrintSetup -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PrintSetup
setup
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSetupUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod PrintSetupUnrefMethodInfo PrintSetup signature where
    overloadedMethod = printSetupUnref

instance O.OverloadedMethodInfo PrintSetupUnrefMethodInfo PrintSetup where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gtk.Structs.PrintSetup.printSetupUnref",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk-4.0.9/docs/GI-Gtk-Structs-PrintSetup.html#v:printSetupUnref"
        })


#endif

#if defined(ENABLE_OVERLOADING)
type family ResolvePrintSetupMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolvePrintSetupMethod "ref" o = PrintSetupRefMethodInfo
    ResolvePrintSetupMethod "unref" o = PrintSetupUnrefMethodInfo
    ResolvePrintSetupMethod "getPageSetup" o = PrintSetupGetPageSetupMethodInfo
    ResolvePrintSetupMethod "getPrintSettings" o = PrintSetupGetPrintSettingsMethodInfo
    ResolvePrintSetupMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#endif