{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A GtkPageSetup object stores the page size, orientation and margins.
-- The idea is that you can get one of these from the page setup dialog
-- and then pass it to the t'GI.Gtk.Objects.PrintOperation.PrintOperation' when printing.
-- The benefit of splitting this out of the t'GI.Gtk.Objects.PrintSettings.PrintSettings' is that
-- these affect the actual layout of the page, and thus need to be set
-- long before user prints.
-- 
-- ## Margins ## {@/print/@-margins}
-- The margins specified in this object are the “print margins”, i.e. the
-- parts of the page that the printer cannot print on. These are different
-- from the layout margins that a word processor uses; they are typically
-- used to determine the minimal size for the layout
-- margins.
-- 
-- To obtain a t'GI.Gtk.Objects.PageSetup.PageSetup' use 'GI.Gtk.Objects.PageSetup.pageSetupNew' to get the defaults,
-- or use 'GI.Gtk.Functions.printRunPageSetupDialog' to show the page setup dialog
-- and receive the resulting page setup.
-- 
-- == A page setup dialog
-- 
-- 
-- === /C code/
-- >
-- >static GtkPrintSettings *settings = NULL;
-- >static GtkPageSetup *page_setup = NULL;
-- >
-- >static void
-- >do_page_setup (void)
-- >{
-- >  GtkPageSetup *new_page_setup;
-- >
-- >  if (settings == NULL)
-- >    settings = gtk_print_settings_new ();
-- >
-- >  new_page_setup = gtk_print_run_page_setup_dialog (GTK_WINDOW (main_window),
-- >                                                    page_setup, settings);
-- >
-- >  if (page_setup)
-- >    g_object_unref (page_setup);
-- >
-- >  page_setup = new_page_setup;
-- >}
-- 
-- 
-- Printing support was added in GTK+ 2.10.

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

module GI.Gtk.Objects.PageSetup
    ( 

-- * Exported types
    PageSetup(..)                           ,
    IsPageSetup                             ,
    toPageSetup                             ,
    noPageSetup                             ,


 -- * Methods
-- ** Overloaded methods #method:Overloaded methods#

#if defined(ENABLE_OVERLOADING)
    ResolvePageSetupMethod                  ,
#endif


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    PageSetupCopyMethodInfo                 ,
#endif
    pageSetupCopy                           ,


-- ** getBottomMargin #method:getBottomMargin#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetBottomMarginMethodInfo      ,
#endif
    pageSetupGetBottomMargin                ,


-- ** getLeftMargin #method:getLeftMargin#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetLeftMarginMethodInfo        ,
#endif
    pageSetupGetLeftMargin                  ,


-- ** getOrientation #method:getOrientation#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetOrientationMethodInfo       ,
#endif
    pageSetupGetOrientation                 ,


-- ** getPageHeight #method:getPageHeight#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetPageHeightMethodInfo        ,
#endif
    pageSetupGetPageHeight                  ,


-- ** getPageWidth #method:getPageWidth#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetPageWidthMethodInfo         ,
#endif
    pageSetupGetPageWidth                   ,


-- ** getPaperHeight #method:getPaperHeight#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetPaperHeightMethodInfo       ,
#endif
    pageSetupGetPaperHeight                 ,


-- ** getPaperSize #method:getPaperSize#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetPaperSizeMethodInfo         ,
#endif
    pageSetupGetPaperSize                   ,


-- ** getPaperWidth #method:getPaperWidth#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetPaperWidthMethodInfo        ,
#endif
    pageSetupGetPaperWidth                  ,


-- ** getRightMargin #method:getRightMargin#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetRightMarginMethodInfo       ,
#endif
    pageSetupGetRightMargin                 ,


-- ** getTopMargin #method:getTopMargin#

#if defined(ENABLE_OVERLOADING)
    PageSetupGetTopMarginMethodInfo         ,
#endif
    pageSetupGetTopMargin                   ,


-- ** loadFile #method:loadFile#

#if defined(ENABLE_OVERLOADING)
    PageSetupLoadFileMethodInfo             ,
#endif
    pageSetupLoadFile                       ,


-- ** loadKeyFile #method:loadKeyFile#

#if defined(ENABLE_OVERLOADING)
    PageSetupLoadKeyFileMethodInfo          ,
#endif
    pageSetupLoadKeyFile                    ,


-- ** new #method:new#

    pageSetupNew                            ,


-- ** newFromFile #method:newFromFile#

    pageSetupNewFromFile                    ,


-- ** newFromGvariant #method:newFromGvariant#

    pageSetupNewFromGvariant                ,


-- ** newFromKeyFile #method:newFromKeyFile#

    pageSetupNewFromKeyFile                 ,


-- ** setBottomMargin #method:setBottomMargin#

#if defined(ENABLE_OVERLOADING)
    PageSetupSetBottomMarginMethodInfo      ,
#endif
    pageSetupSetBottomMargin                ,


-- ** setLeftMargin #method:setLeftMargin#

#if defined(ENABLE_OVERLOADING)
    PageSetupSetLeftMarginMethodInfo        ,
#endif
    pageSetupSetLeftMargin                  ,


-- ** setOrientation #method:setOrientation#

#if defined(ENABLE_OVERLOADING)
    PageSetupSetOrientationMethodInfo       ,
#endif
    pageSetupSetOrientation                 ,


-- ** setPaperSize #method:setPaperSize#

#if defined(ENABLE_OVERLOADING)
    PageSetupSetPaperSizeMethodInfo         ,
#endif
    pageSetupSetPaperSize                   ,


-- ** setPaperSizeAndDefaultMargins #method:setPaperSizeAndDefaultMargins#

#if defined(ENABLE_OVERLOADING)
    PageSetupSetPaperSizeAndDefaultMarginsMethodInfo,
#endif
    pageSetupSetPaperSizeAndDefaultMargins  ,


-- ** setRightMargin #method:setRightMargin#

#if defined(ENABLE_OVERLOADING)
    PageSetupSetRightMarginMethodInfo       ,
#endif
    pageSetupSetRightMargin                 ,


-- ** setTopMargin #method:setTopMargin#

#if defined(ENABLE_OVERLOADING)
    PageSetupSetTopMarginMethodInfo         ,
#endif
    pageSetupSetTopMargin                   ,


-- ** toFile #method:toFile#

#if defined(ENABLE_OVERLOADING)
    PageSetupToFileMethodInfo               ,
#endif
    pageSetupToFile                         ,


-- ** toGvariant #method:toGvariant#

#if defined(ENABLE_OVERLOADING)
    PageSetupToGvariantMethodInfo           ,
#endif
    pageSetupToGvariant                     ,


-- ** toKeyFile #method:toKeyFile#

#if defined(ENABLE_OVERLOADING)
    PageSetupToKeyFileMethodInfo            ,
#endif
    pageSetupToKeyFile                      ,




    ) 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.ManagedPtr as B.ManagedPtr
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 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 GI.GLib.Structs.KeyFile as GLib.KeyFile
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Structs.PaperSize as Gtk.PaperSize

-- | Memory-managed wrapper type.
newtype PageSetup = PageSetup (ManagedPtr PageSetup)
    deriving (PageSetup -> PageSetup -> Bool
(PageSetup -> PageSetup -> Bool)
-> (PageSetup -> PageSetup -> Bool) -> Eq PageSetup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PageSetup -> PageSetup -> Bool
$c/= :: PageSetup -> PageSetup -> Bool
== :: PageSetup -> PageSetup -> Bool
$c== :: PageSetup -> PageSetup -> Bool
Eq)
foreign import ccall "gtk_page_setup_get_type"
    c_gtk_page_setup_get_type :: IO GType

instance GObject PageSetup where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_page_setup_get_type
    

-- | Convert 'PageSetup' to and from 'Data.GI.Base.GValue.GValue' with 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
instance B.GValue.IsGValue PageSetup where
    toGValue :: PageSetup -> IO GValue
toGValue o :: PageSetup
o = do
        GType
gtype <- IO GType
c_gtk_page_setup_get_type
        PageSetup -> (Ptr PageSetup -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PageSetup
o (GType
-> (GValue -> Ptr PageSetup -> IO ()) -> Ptr PageSetup -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr PageSetup -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO PageSetup
fromGValue gv :: GValue
gv = do
        Ptr PageSetup
ptr <- GValue -> IO (Ptr PageSetup)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr PageSetup)
        (ManagedPtr PageSetup -> PageSetup)
-> Ptr PageSetup -> IO PageSetup
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr PageSetup -> PageSetup
PageSetup Ptr PageSetup
ptr
        
    

-- | Type class for types which can be safely cast to `PageSetup`, for instance with `toPageSetup`.
class (GObject o, O.IsDescendantOf PageSetup o) => IsPageSetup o
instance (GObject o, O.IsDescendantOf PageSetup o) => IsPageSetup o

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

-- | Cast to `PageSetup`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toPageSetup :: (MonadIO m, IsPageSetup o) => o -> m PageSetup
toPageSetup :: o -> m PageSetup
toPageSetup = IO PageSetup -> m PageSetup
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PageSetup -> m PageSetup)
-> (o -> IO PageSetup) -> o -> m PageSetup
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr PageSetup -> PageSetup) -> o -> IO PageSetup
forall o o'.
(HasCallStack, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr PageSetup -> PageSetup
PageSetup

-- | A convenience alias for `Nothing` :: `Maybe` `PageSetup`.
noPageSetup :: Maybe PageSetup
noPageSetup :: Maybe PageSetup
noPageSetup = Maybe PageSetup
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolvePageSetupMethod (t :: Symbol) (o :: *) :: * where
    ResolvePageSetupMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePageSetupMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePageSetupMethod "copy" o = PageSetupCopyMethodInfo
    ResolvePageSetupMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePageSetupMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePageSetupMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePageSetupMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePageSetupMethod "loadFile" o = PageSetupLoadFileMethodInfo
    ResolvePageSetupMethod "loadKeyFile" o = PageSetupLoadKeyFileMethodInfo
    ResolvePageSetupMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePageSetupMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePageSetupMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePageSetupMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePageSetupMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePageSetupMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePageSetupMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePageSetupMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePageSetupMethod "toFile" o = PageSetupToFileMethodInfo
    ResolvePageSetupMethod "toGvariant" o = PageSetupToGvariantMethodInfo
    ResolvePageSetupMethod "toKeyFile" o = PageSetupToKeyFileMethodInfo
    ResolvePageSetupMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePageSetupMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePageSetupMethod "getBottomMargin" o = PageSetupGetBottomMarginMethodInfo
    ResolvePageSetupMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePageSetupMethod "getLeftMargin" o = PageSetupGetLeftMarginMethodInfo
    ResolvePageSetupMethod "getOrientation" o = PageSetupGetOrientationMethodInfo
    ResolvePageSetupMethod "getPageHeight" o = PageSetupGetPageHeightMethodInfo
    ResolvePageSetupMethod "getPageWidth" o = PageSetupGetPageWidthMethodInfo
    ResolvePageSetupMethod "getPaperHeight" o = PageSetupGetPaperHeightMethodInfo
    ResolvePageSetupMethod "getPaperSize" o = PageSetupGetPaperSizeMethodInfo
    ResolvePageSetupMethod "getPaperWidth" o = PageSetupGetPaperWidthMethodInfo
    ResolvePageSetupMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePageSetupMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePageSetupMethod "getRightMargin" o = PageSetupGetRightMarginMethodInfo
    ResolvePageSetupMethod "getTopMargin" o = PageSetupGetTopMarginMethodInfo
    ResolvePageSetupMethod "setBottomMargin" o = PageSetupSetBottomMarginMethodInfo
    ResolvePageSetupMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePageSetupMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePageSetupMethod "setLeftMargin" o = PageSetupSetLeftMarginMethodInfo
    ResolvePageSetupMethod "setOrientation" o = PageSetupSetOrientationMethodInfo
    ResolvePageSetupMethod "setPaperSize" o = PageSetupSetPaperSizeMethodInfo
    ResolvePageSetupMethod "setPaperSizeAndDefaultMargins" o = PageSetupSetPaperSizeAndDefaultMarginsMethodInfo
    ResolvePageSetupMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePageSetupMethod "setRightMargin" o = PageSetupSetRightMarginMethodInfo
    ResolvePageSetupMethod "setTopMargin" o = PageSetupSetTopMarginMethodInfo
    ResolvePageSetupMethod l o = O.MethodResolutionFailed l o

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

#endif

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

#if defined(ENABLE_OVERLOADING)
#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList PageSetup = PageSetupSignalList
type PageSetupSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])

#endif

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

foreign import ccall "gtk_page_setup_new" gtk_page_setup_new :: 
    IO (Ptr PageSetup)

-- | Creates a new t'GI.Gtk.Objects.PageSetup.PageSetup'.
-- 
-- /Since: 2.10/
pageSetupNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m PageSetup
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.PageSetup.PageSetup'.
pageSetupNew :: m PageSetup
pageSetupNew  = IO PageSetup -> m PageSetup
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 PageSetup
result <- IO (Ptr PageSetup)
gtk_page_setup_new
    Text -> Ptr PageSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "pageSetupNew" 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
wrapObject ManagedPtr PageSetup -> PageSetup
PageSetup) Ptr PageSetup
result
    PageSetup -> IO PageSetup
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PageSetup::new_from_file
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "file_name"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the filename to read the page setup from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "PageSetup" })
-- throws : True
-- Skip return : False

foreign import ccall "gtk_page_setup_new_from_file" gtk_page_setup_new_from_file :: 
    CString ->                              -- file_name : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr PageSetup)

-- | Reads the page setup from the file /@fileName@/. Returns a
-- new t'GI.Gtk.Objects.PageSetup.PageSetup' object with the restored page setup,
-- or 'P.Nothing' if an error occurred. See 'GI.Gtk.Objects.PageSetup.pageSetupToFile'.
-- 
-- /Since: 2.12/
pageSetupNewFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@fileName@/: the filename to read the page setup from
    -> m PageSetup
    -- ^ __Returns:__ the restored t'GI.Gtk.Objects.PageSetup.PageSetup' /(Can throw 'Data.GI.Base.GError.GError')/
pageSetupNewFromFile :: [Char] -> m PageSetup
pageSetupNewFromFile fileName :: [Char]
fileName = IO PageSetup -> m PageSetup
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
    CString
fileName' <- [Char] -> IO CString
stringToCString [Char]
fileName
    IO PageSetup -> IO () -> IO PageSetup
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr PageSetup
result <- (Ptr (Ptr GError) -> IO (Ptr PageSetup)) -> IO (Ptr PageSetup)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr PageSetup)) -> IO (Ptr PageSetup))
-> (Ptr (Ptr GError) -> IO (Ptr PageSetup)) -> IO (Ptr PageSetup)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr PageSetup)
gtk_page_setup_new_from_file CString
fileName'
        Text -> Ptr PageSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "pageSetupNewFromFile" 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
wrapObject ManagedPtr PageSetup -> PageSetup
PageSetup) Ptr PageSetup
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fileName'
        PageSetup -> IO PageSetup
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fileName'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method PageSetup::new_from_gvariant
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "variant"
--           , argType = TVariant
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an a{sv} #GVariant" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "PageSetup" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_new_from_gvariant" gtk_page_setup_new_from_gvariant :: 
    Ptr GVariant ->                         -- variant : TVariant
    IO (Ptr PageSetup)

-- | Desrialize a page setup from an a{sv} variant in
-- the format produced by 'GI.Gtk.Objects.PageSetup.pageSetupToGvariant'.
-- 
-- /Since: 3.22/
pageSetupNewFromGvariant ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GVariant
    -- ^ /@variant@/: an a{sv} t'GVariant'
    -> m PageSetup
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.PageSetup.PageSetup' object
pageSetupNewFromGvariant :: GVariant -> m PageSetup
pageSetupNewFromGvariant variant :: GVariant
variant = IO PageSetup -> m PageSetup
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 GVariant
variant' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
variant
    Ptr PageSetup
result <- Ptr GVariant -> IO (Ptr PageSetup)
gtk_page_setup_new_from_gvariant Ptr GVariant
variant'
    Text -> Ptr PageSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "pageSetupNewFromGvariant" 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
wrapObject ManagedPtr PageSetup -> PageSetup
PageSetup) Ptr PageSetup
result
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
variant
    PageSetup -> IO PageSetup
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PageSetup::new_from_key_file
-- method type : Constructor
-- Args: [ Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GKeyFile to retrieve the page_setup from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of the group in the key_file to read, or %NULL\n             to use the default name \8220Page Setup\8221"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gtk" , name = "PageSetup" })
-- throws : True
-- Skip return : False

foreign import ccall "gtk_page_setup_new_from_key_file" gtk_page_setup_new_from_key_file :: 
    Ptr GLib.KeyFile.KeyFile ->             -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO (Ptr PageSetup)

-- | Reads the page setup from the group /@groupName@/ in the key file
-- /@keyFile@/. Returns a new t'GI.Gtk.Objects.PageSetup.PageSetup' object with the restored
-- page setup, or 'P.Nothing' if an error occurred.
-- 
-- /Since: 2.12/
pageSetupNewFromKeyFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.KeyFile.KeyFile
    -- ^ /@keyFile@/: the t'GI.GLib.Structs.KeyFile.KeyFile' to retrieve the page_setup from
    -> Maybe (T.Text)
    -- ^ /@groupName@/: the name of the group in the key_file to read, or 'P.Nothing'
    --              to use the default name “Page Setup”
    -> m PageSetup
    -- ^ __Returns:__ the restored t'GI.Gtk.Objects.PageSetup.PageSetup' /(Can throw 'Data.GI.Base.GError.GError')/
pageSetupNewFromKeyFile :: KeyFile -> Maybe Text -> m PageSetup
pageSetupNewFromKeyFile keyFile :: KeyFile
keyFile groupName :: Maybe Text
groupName = IO PageSetup -> m PageSetup
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 KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
maybeGroupName <- case Maybe Text
groupName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jGroupName :: Text
jGroupName -> do
            CString
jGroupName' <- Text -> IO CString
textToCString Text
jGroupName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGroupName'
    IO PageSetup -> IO () -> IO PageSetup
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr PageSetup
result <- (Ptr (Ptr GError) -> IO (Ptr PageSetup)) -> IO (Ptr PageSetup)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr PageSetup)) -> IO (Ptr PageSetup))
-> (Ptr (Ptr GError) -> IO (Ptr PageSetup)) -> IO (Ptr PageSetup)
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile -> CString -> Ptr (Ptr GError) -> IO (Ptr PageSetup)
gtk_page_setup_new_from_key_file Ptr KeyFile
keyFile' CString
maybeGroupName
        Text -> Ptr PageSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "pageSetupNewFromKeyFile" 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
wrapObject ManagedPtr PageSetup -> PageSetup
PageSetup) Ptr PageSetup
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
        PageSetup -> IO PageSetup
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
     )

#if defined(ENABLE_OVERLOADING)
#endif

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

foreign import ccall "gtk_page_setup_copy" gtk_page_setup_copy :: 
    Ptr PageSetup ->                        -- other : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    IO (Ptr PageSetup)

-- | Copies a t'GI.Gtk.Objects.PageSetup.PageSetup'.
-- 
-- /Since: 2.10/
pageSetupCopy ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@other@/: the t'GI.Gtk.Objects.PageSetup.PageSetup' to copy
    -> m PageSetup
    -- ^ __Returns:__ a copy of /@other@/
pageSetupCopy :: a -> m PageSetup
pageSetupCopy other :: a
other = IO PageSetup -> m PageSetup
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 PageSetup
other' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
other
    Ptr PageSetup
result <- Ptr PageSetup -> IO (Ptr PageSetup)
gtk_page_setup_copy Ptr PageSetup
other'
    Text -> Ptr PageSetup -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "pageSetupCopy" 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
wrapObject ManagedPtr PageSetup -> PageSetup
PageSetup) Ptr PageSetup
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
other
    PageSetup -> IO PageSetup
forall (m :: * -> *) a. Monad m => a -> m a
return PageSetup
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupCopyMethodInfo
instance (signature ~ (m PageSetup), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupCopyMethodInfo a signature where
    overloadedMethod = pageSetupCopy

#endif

-- method PageSetup::get_bottom_margin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unit for the return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_get_bottom_margin" gtk_page_setup_get_bottom_margin :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Gets the bottom margin in units of /@unit@/.
-- 
-- /Since: 2.10/
pageSetupGetBottomMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the bottom margin
pageSetupGetBottomMargin :: a -> Unit -> m Double
pageSetupGetBottomMargin setup :: a
setup unit :: Unit
unit = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    CDouble
result <- Ptr PageSetup -> CUInt -> IO CDouble
gtk_page_setup_get_bottom_margin Ptr PageSetup
setup' CUInt
unit'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetBottomMarginMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetBottomMarginMethodInfo a signature where
    overloadedMethod = pageSetupGetBottomMargin

#endif

-- method PageSetup::get_left_margin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unit for the return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_get_left_margin" gtk_page_setup_get_left_margin :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Gets the left margin in units of /@unit@/.
-- 
-- /Since: 2.10/
pageSetupGetLeftMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the left margin
pageSetupGetLeftMargin :: a -> Unit -> m Double
pageSetupGetLeftMargin setup :: a
setup unit :: Unit
unit = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    CDouble
result <- Ptr PageSetup -> CUInt -> IO CDouble
gtk_page_setup_get_left_margin Ptr PageSetup
setup' CUInt
unit'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetLeftMarginMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetLeftMarginMethodInfo a signature where
    overloadedMethod = pageSetupGetLeftMargin

#endif

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

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

-- | Gets the page orientation of the t'GI.Gtk.Objects.PageSetup.PageSetup'.
-- 
-- /Since: 2.10/
pageSetupGetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> m Gtk.Enums.PageOrientation
    -- ^ __Returns:__ the page orientation
pageSetupGetOrientation :: a -> m PageOrientation
pageSetupGetOrientation setup :: a
setup = IO PageOrientation -> m PageOrientation
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PageOrientation -> m PageOrientation)
-> IO PageOrientation -> m PageOrientation
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    CUInt
result <- Ptr PageSetup -> IO CUInt
gtk_page_setup_get_orientation Ptr PageSetup
setup'
    let result' :: PageOrientation
result' = (Int -> PageOrientation
forall a. Enum a => Int -> a
toEnum (Int -> PageOrientation)
-> (CUInt -> Int) -> CUInt -> PageOrientation
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
setup
    PageOrientation -> IO PageOrientation
forall (m :: * -> *) a. Monad m => a -> m a
return PageOrientation
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetOrientationMethodInfo
instance (signature ~ (m Gtk.Enums.PageOrientation), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetOrientationMethodInfo a signature where
    overloadedMethod = pageSetupGetOrientation

#endif

-- method PageSetup::get_page_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unit for the return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_get_page_height" gtk_page_setup_get_page_height :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Returns the page height in units of /@unit@/.
-- 
-- Note that this function takes orientation and
-- margins into consideration.
-- See 'GI.Gtk.Objects.PageSetup.pageSetupGetPaperHeight'.
-- 
-- /Since: 2.10/
pageSetupGetPageHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the page height.
pageSetupGetPageHeight :: a -> Unit -> m Double
pageSetupGetPageHeight setup :: a
setup unit :: Unit
unit = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    CDouble
result <- Ptr PageSetup -> CUInt -> IO CDouble
gtk_page_setup_get_page_height Ptr PageSetup
setup' CUInt
unit'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetPageHeightMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetPageHeightMethodInfo a signature where
    overloadedMethod = pageSetupGetPageHeight

#endif

-- method PageSetup::get_page_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unit for the return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_get_page_width" gtk_page_setup_get_page_width :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Returns the page width in units of /@unit@/.
-- 
-- Note that this function takes orientation and
-- margins into consideration.
-- See 'GI.Gtk.Objects.PageSetup.pageSetupGetPaperWidth'.
-- 
-- /Since: 2.10/
pageSetupGetPageWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the page width.
pageSetupGetPageWidth :: a -> Unit -> m Double
pageSetupGetPageWidth setup :: a
setup unit :: Unit
unit = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    CDouble
result <- Ptr PageSetup -> CUInt -> IO CDouble
gtk_page_setup_get_page_width Ptr PageSetup
setup' CUInt
unit'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetPageWidthMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetPageWidthMethodInfo a signature where
    overloadedMethod = pageSetupGetPageWidth

#endif

-- method PageSetup::get_paper_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unit for the return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_get_paper_height" gtk_page_setup_get_paper_height :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Returns the paper height in units of /@unit@/.
-- 
-- Note that this function takes orientation, but
-- not margins into consideration.
-- See 'GI.Gtk.Objects.PageSetup.pageSetupGetPageHeight'.
-- 
-- /Since: 2.10/
pageSetupGetPaperHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the paper height.
pageSetupGetPaperHeight :: a -> Unit -> m Double
pageSetupGetPaperHeight setup :: a
setup unit :: Unit
unit = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    CDouble
result <- Ptr PageSetup -> CUInt -> IO CDouble
gtk_page_setup_get_paper_height Ptr PageSetup
setup' CUInt
unit'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetPaperHeightMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetPaperHeightMethodInfo a signature where
    overloadedMethod = pageSetupGetPaperHeight

#endif

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

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

-- | Gets the paper size of the t'GI.Gtk.Objects.PageSetup.PageSetup'.
-- 
-- /Since: 2.10/
pageSetupGetPaperSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> m Gtk.PaperSize.PaperSize
    -- ^ __Returns:__ the paper size
pageSetupGetPaperSize :: a -> m PaperSize
pageSetupGetPaperSize setup :: a
setup = IO PaperSize -> m PaperSize
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PaperSize -> m PaperSize) -> IO PaperSize -> m PaperSize
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    Ptr PaperSize
result <- Ptr PageSetup -> IO (Ptr PaperSize)
gtk_page_setup_get_paper_size Ptr PageSetup
setup'
    Text -> Ptr PaperSize -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "pageSetupGetPaperSize" Ptr PaperSize
result
    PaperSize
result' <- ((ManagedPtr PaperSize -> PaperSize)
-> Ptr PaperSize -> IO PaperSize
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr PaperSize -> PaperSize
Gtk.PaperSize.PaperSize) Ptr PaperSize
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    PaperSize -> IO PaperSize
forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetPaperSizeMethodInfo
instance (signature ~ (m Gtk.PaperSize.PaperSize), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetPaperSizeMethodInfo a signature where
    overloadedMethod = pageSetupGetPaperSize

#endif

-- method PageSetup::get_paper_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unit for the return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_get_paper_width" gtk_page_setup_get_paper_width :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Returns the paper width in units of /@unit@/.
-- 
-- Note that this function takes orientation, but
-- not margins into consideration.
-- See 'GI.Gtk.Objects.PageSetup.pageSetupGetPageWidth'.
-- 
-- /Since: 2.10/
pageSetupGetPaperWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the paper width.
pageSetupGetPaperWidth :: a -> Unit -> m Double
pageSetupGetPaperWidth setup :: a
setup unit :: Unit
unit = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    CDouble
result <- Ptr PageSetup -> CUInt -> IO CDouble
gtk_page_setup_get_paper_width Ptr PageSetup
setup' CUInt
unit'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetPaperWidthMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetPaperWidthMethodInfo a signature where
    overloadedMethod = pageSetupGetPaperWidth

#endif

-- method PageSetup::get_right_margin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unit for the return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_get_right_margin" gtk_page_setup_get_right_margin :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Gets the right margin in units of /@unit@/.
-- 
-- /Since: 2.10/
pageSetupGetRightMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the right margin
pageSetupGetRightMargin :: a -> Unit -> m Double
pageSetupGetRightMargin setup :: a
setup unit :: Unit
unit = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    CDouble
result <- Ptr PageSetup -> CUInt -> IO CDouble
gtk_page_setup_get_right_margin Ptr PageSetup
setup' CUInt
unit'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetRightMarginMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetRightMarginMethodInfo a signature where
    overloadedMethod = pageSetupGetRightMargin

#endif

-- method PageSetup::get_top_margin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the unit for the return value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TDouble)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_get_top_margin" gtk_page_setup_get_top_margin :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Gets the top margin in units of /@unit@/.
-- 
-- /Since: 2.10/
pageSetupGetTopMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the top margin
pageSetupGetTopMargin :: a -> Unit -> m Double
pageSetupGetTopMargin setup :: a
setup unit :: Unit
unit = IO Double -> m Double
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Double -> m Double) -> IO Double -> m Double
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    CDouble
result <- Ptr PageSetup -> CUInt -> IO CDouble
gtk_page_setup_get_top_margin Ptr PageSetup
setup' CUInt
unit'
    let result' :: Double
result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupGetTopMarginMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupGetTopMarginMethodInfo a signature where
    overloadedMethod = pageSetupGetTopMargin

#endif

-- method PageSetup::load_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file_name"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the filename to read the page setup from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gtk_page_setup_load_file" gtk_page_setup_load_file :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CString ->                              -- file_name : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Reads the page setup from the file /@fileName@/.
-- See 'GI.Gtk.Objects.PageSetup.pageSetupToFile'.
-- 
-- /Since: 2.14/
pageSetupLoadFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> [Char]
    -- ^ /@fileName@/: the filename to read the page setup from
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pageSetupLoadFile :: a -> [Char] -> m ()
pageSetupLoadFile setup :: a
setup fileName :: [Char]
fileName = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    CString
fileName' <- [Char] -> IO CString
stringToCString [Char]
fileName
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr PageSetup -> CString -> Ptr (Ptr GError) -> IO CInt
gtk_page_setup_load_file Ptr PageSetup
setup' CString
fileName'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fileName'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fileName'
     )

#if defined(ENABLE_OVERLOADING)
data PageSetupLoadFileMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupLoadFileMethodInfo a signature where
    overloadedMethod = pageSetupLoadFile

#endif

-- method PageSetup::load_key_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GKeyFile to retrieve the page_setup from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the name of the group in the key_file to read, or %NULL\n             to use the default name \8220Page Setup\8221"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gtk_page_setup_load_key_file" gtk_page_setup_load_key_file :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    Ptr GLib.KeyFile.KeyFile ->             -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Reads the page setup from the group /@groupName@/ in the key file
-- /@keyFile@/.
-- 
-- /Since: 2.14/
pageSetupLoadKeyFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> GLib.KeyFile.KeyFile
    -- ^ /@keyFile@/: the t'GI.GLib.Structs.KeyFile.KeyFile' to retrieve the page_setup from
    -> Maybe (T.Text)
    -- ^ /@groupName@/: the name of the group in the key_file to read, or 'P.Nothing'
    --              to use the default name “Page Setup”
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pageSetupLoadKeyFile :: a -> KeyFile -> Maybe Text -> m ()
pageSetupLoadKeyFile setup :: a
setup keyFile :: KeyFile
keyFile groupName :: Maybe Text
groupName = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
maybeGroupName <- case Maybe Text
groupName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jGroupName :: Text
jGroupName -> do
            CString
jGroupName' <- Text -> IO CString
textToCString Text
jGroupName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGroupName'
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr PageSetup
-> Ptr KeyFile -> CString -> Ptr (Ptr GError) -> IO CInt
gtk_page_setup_load_key_file Ptr PageSetup
setup' Ptr KeyFile
keyFile' CString
maybeGroupName
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
     )

#if defined(ENABLE_OVERLOADING)
data PageSetupLoadKeyFileMethodInfo
instance (signature ~ (GLib.KeyFile.KeyFile -> Maybe (T.Text) -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupLoadKeyFileMethodInfo a signature where
    overloadedMethod = pageSetupLoadKeyFile

#endif

-- method PageSetup::set_bottom_margin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "margin"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new bottom margin in units of @unit"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the units for @margin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_set_bottom_margin" gtk_page_setup_set_bottom_margin :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CDouble ->                              -- margin : TBasicType TDouble
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO ()

-- | Sets the bottom margin of the t'GI.Gtk.Objects.PageSetup.PageSetup'.
-- 
-- /Since: 2.10/
pageSetupSetBottomMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Double
    -- ^ /@margin@/: the new bottom margin in units of /@unit@/
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the units for /@margin@/
    -> m ()
pageSetupSetBottomMargin :: a -> Double -> Unit -> m ()
pageSetupSetBottomMargin setup :: a
setup margin :: Double
margin unit :: Unit
unit = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let margin' :: CDouble
margin' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
margin
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    Ptr PageSetup -> CDouble -> CUInt -> IO ()
gtk_page_setup_set_bottom_margin Ptr PageSetup
setup' CDouble
margin' CUInt
unit'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PageSetupSetBottomMarginMethodInfo
instance (signature ~ (Double -> Gtk.Enums.Unit -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupSetBottomMarginMethodInfo a signature where
    overloadedMethod = pageSetupSetBottomMargin

#endif

-- method PageSetup::set_left_margin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "margin"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new left margin in units of @unit"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the units for @margin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_set_left_margin" gtk_page_setup_set_left_margin :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CDouble ->                              -- margin : TBasicType TDouble
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO ()

-- | Sets the left margin of the t'GI.Gtk.Objects.PageSetup.PageSetup'.
-- 
-- /Since: 2.10/
pageSetupSetLeftMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Double
    -- ^ /@margin@/: the new left margin in units of /@unit@/
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the units for /@margin@/
    -> m ()
pageSetupSetLeftMargin :: a -> Double -> Unit -> m ()
pageSetupSetLeftMargin setup :: a
setup margin :: Double
margin unit :: Unit
unit = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let margin' :: CDouble
margin' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
margin
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    Ptr PageSetup -> CDouble -> CUInt -> IO ()
gtk_page_setup_set_left_margin Ptr PageSetup
setup' CDouble
margin' CUInt
unit'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PageSetupSetLeftMarginMethodInfo
instance (signature ~ (Double -> Gtk.Enums.Unit -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupSetLeftMarginMethodInfo a signature where
    overloadedMethod = pageSetupSetLeftMargin

#endif

-- method PageSetup::set_orientation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "orientation"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageOrientation" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageOrientation value"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_set_orientation" gtk_page_setup_set_orientation :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CUInt ->                                -- orientation : TInterface (Name {namespace = "Gtk", name = "PageOrientation"})
    IO ()

-- | Sets the page orientation of the t'GI.Gtk.Objects.PageSetup.PageSetup'.
-- 
-- /Since: 2.10/
pageSetupSetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.Enums.PageOrientation
    -- ^ /@orientation@/: a t'GI.Gtk.Enums.PageOrientation' value
    -> m ()
pageSetupSetOrientation :: a -> PageOrientation -> m ()
pageSetupSetOrientation setup :: a
setup orientation :: PageOrientation
orientation = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let orientation' :: CUInt
orientation' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (PageOrientation -> Int) -> PageOrientation -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageOrientation -> Int
forall a. Enum a => a -> Int
fromEnum) PageOrientation
orientation
    Ptr PageSetup -> CUInt -> IO ()
gtk_page_setup_set_orientation Ptr PageSetup
setup' CUInt
orientation'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PageSetupSetOrientationMethodInfo
instance (signature ~ (Gtk.Enums.PageOrientation -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupSetOrientationMethodInfo a signature where
    overloadedMethod = pageSetupSetOrientation

#endif

-- method PageSetup::set_paper_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PaperSize" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPaperSize" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Sets the paper size of the t'GI.Gtk.Objects.PageSetup.PageSetup' without
-- changing the margins. See
-- 'GI.Gtk.Objects.PageSetup.pageSetupSetPaperSizeAndDefaultMargins'.
-- 
-- /Since: 2.10/
pageSetupSetPaperSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.PaperSize.PaperSize
    -- ^ /@size@/: a t'GI.Gtk.Structs.PaperSize.PaperSize'
    -> m ()
pageSetupSetPaperSize :: a -> PaperSize -> m ()
pageSetupSetPaperSize setup :: a
setup size :: PaperSize
size = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    Ptr PaperSize
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
    Ptr PageSetup -> Ptr PaperSize -> IO ()
gtk_page_setup_set_paper_size Ptr PageSetup
setup' Ptr PaperSize
size'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    PaperSize -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PaperSize
size
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PageSetupSetPaperSizeMethodInfo
instance (signature ~ (Gtk.PaperSize.PaperSize -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupSetPaperSizeMethodInfo a signature where
    overloadedMethod = pageSetupSetPaperSize

#endif

-- method PageSetup::set_paper_size_and_default_margins
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "size"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PaperSize" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPaperSize" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

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

-- | Sets the paper size of the t'GI.Gtk.Objects.PageSetup.PageSetup' and modifies
-- the margins according to the new paper size.
-- 
-- /Since: 2.10/
pageSetupSetPaperSizeAndDefaultMargins ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Gtk.PaperSize.PaperSize
    -- ^ /@size@/: a t'GI.Gtk.Structs.PaperSize.PaperSize'
    -> m ()
pageSetupSetPaperSizeAndDefaultMargins :: a -> PaperSize -> m ()
pageSetupSetPaperSizeAndDefaultMargins setup :: a
setup size :: PaperSize
size = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    Ptr PaperSize
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
    Ptr PageSetup -> Ptr PaperSize -> IO ()
gtk_page_setup_set_paper_size_and_default_margins Ptr PageSetup
setup' Ptr PaperSize
size'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    PaperSize -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PaperSize
size
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PageSetupSetPaperSizeAndDefaultMarginsMethodInfo
instance (signature ~ (Gtk.PaperSize.PaperSize -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupSetPaperSizeAndDefaultMarginsMethodInfo a signature where
    overloadedMethod = pageSetupSetPaperSizeAndDefaultMargins

#endif

-- method PageSetup::set_right_margin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "margin"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new right margin in units of @unit"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the units for @margin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_set_right_margin" gtk_page_setup_set_right_margin :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CDouble ->                              -- margin : TBasicType TDouble
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO ()

-- | Sets the right margin of the t'GI.Gtk.Objects.PageSetup.PageSetup'.
-- 
-- /Since: 2.10/
pageSetupSetRightMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Double
    -- ^ /@margin@/: the new right margin in units of /@unit@/
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the units for /@margin@/
    -> m ()
pageSetupSetRightMargin :: a -> Double -> Unit -> m ()
pageSetupSetRightMargin setup :: a
setup margin :: Double
margin unit :: Unit
unit = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let margin' :: CDouble
margin' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
margin
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    Ptr PageSetup -> CDouble -> CUInt -> IO ()
gtk_page_setup_set_right_margin Ptr PageSetup
setup' CDouble
margin' CUInt
unit'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PageSetupSetRightMarginMethodInfo
instance (signature ~ (Double -> Gtk.Enums.Unit -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupSetRightMarginMethodInfo a signature where
    overloadedMethod = pageSetupSetRightMargin

#endif

-- method PageSetup::set_top_margin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "margin"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the new top margin in units of @unit"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "unit"
--           , argType = TInterface Name { namespace = "Gtk" , name = "Unit" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the units for @margin"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_set_top_margin" gtk_page_setup_set_top_margin :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CDouble ->                              -- margin : TBasicType TDouble
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO ()

-- | Sets the top margin of the t'GI.Gtk.Objects.PageSetup.PageSetup'.
-- 
-- /Since: 2.10/
pageSetupSetTopMargin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> Double
    -- ^ /@margin@/: the new top margin in units of /@unit@/
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the units for /@margin@/
    -> m ()
pageSetupSetTopMargin :: a -> Double -> Unit -> m ()
pageSetupSetTopMargin setup :: a
setup margin :: Double
margin unit :: Unit
unit = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    let margin' :: CDouble
margin' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
margin
    let unit' :: CUInt
unit' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (Unit -> Int) -> Unit -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Unit -> Int
forall a. Enum a => a -> Int
fromEnum) Unit
unit
    Ptr PageSetup -> CDouble -> CUInt -> IO ()
gtk_page_setup_set_top_margin Ptr PageSetup
setup' CDouble
margin' CUInt
unit'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PageSetupSetTopMarginMethodInfo
instance (signature ~ (Double -> Gtk.Enums.Unit -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupSetTopMarginMethodInfo a signature where
    overloadedMethod = pageSetupSetTopMargin

#endif

-- method PageSetup::to_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "file_name"
--           , argType = TBasicType TFileName
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the file to save to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : True
-- Skip return : False

foreign import ccall "gtk_page_setup_to_file" gtk_page_setup_to_file :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    CString ->                              -- file_name : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | This function saves the information from /@setup@/ to /@fileName@/.
-- 
-- /Since: 2.12/
pageSetupToFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> [Char]
    -- ^ /@fileName@/: the file to save to
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
pageSetupToFile :: a -> [Char] -> m ()
pageSetupToFile setup :: a
setup fileName :: [Char]
fileName = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    CString
fileName' <- [Char] -> IO CString
stringToCString [Char]
fileName
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr PageSetup -> CString -> Ptr (Ptr GError) -> IO CInt
gtk_page_setup_to_file Ptr PageSetup
setup' CString
fileName'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fileName'
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fileName'
     )

#if defined(ENABLE_OVERLOADING)
data PageSetupToFileMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupToFileMethodInfo a signature where
    overloadedMethod = pageSetupToFile

#endif

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

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

-- | Serialize page setup to an a{sv} variant.
-- 
-- /Since: 3.22/
pageSetupToGvariant ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> m GVariant
    -- ^ __Returns:__ a new, floating, t'GVariant'
pageSetupToGvariant :: a -> m GVariant
pageSetupToGvariant setup :: a
setup = IO GVariant -> m GVariant
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO GVariant -> m GVariant) -> IO GVariant -> m GVariant
forall a b. (a -> b) -> a -> b
$ do
    Ptr PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    Ptr GVariant
result <- Ptr PageSetup -> IO (Ptr GVariant)
gtk_page_setup_to_gvariant Ptr PageSetup
setup'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "pageSetupToGvariant" Ptr GVariant
result
    GVariant
result' <- Ptr GVariant -> IO GVariant
B.GVariant.newGVariantFromPtr Ptr GVariant
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data PageSetupToGvariantMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupToGvariantMethodInfo a signature where
    overloadedMethod = pageSetupToGvariant

#endif

-- method PageSetup::to_key_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "setup"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSetup" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSetup" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key_file"
--           , argType =
--               TInterface Name { namespace = "GLib" , name = "KeyFile" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the #GKeyFile to save the page setup to"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "group_name"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "the group to add the settings to in @key_file,\n     or %NULL to use the default name \8220Page Setup\8221"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_page_setup_to_key_file" gtk_page_setup_to_key_file :: 
    Ptr PageSetup ->                        -- setup : TInterface (Name {namespace = "Gtk", name = "PageSetup"})
    Ptr GLib.KeyFile.KeyFile ->             -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    IO ()

-- | This function adds the page setup from /@setup@/ to /@keyFile@/.
-- 
-- /Since: 2.12/
pageSetupToKeyFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsPageSetup a) =>
    a
    -- ^ /@setup@/: a t'GI.Gtk.Objects.PageSetup.PageSetup'
    -> GLib.KeyFile.KeyFile
    -- ^ /@keyFile@/: the t'GI.GLib.Structs.KeyFile.KeyFile' to save the page setup to
    -> Maybe (T.Text)
    -- ^ /@groupName@/: the group to add the settings to in /@keyFile@/,
    --      or 'P.Nothing' to use the default name “Page Setup”
    -> m ()
pageSetupToKeyFile :: a -> KeyFile -> Maybe Text -> m ()
pageSetupToKeyFile setup :: a
setup keyFile :: KeyFile
keyFile groupName :: Maybe Text
groupName = 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 PageSetup
setup' <- a -> IO (Ptr PageSetup)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
setup
    Ptr KeyFile
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
    CString
maybeGroupName <- case Maybe Text
groupName of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jGroupName :: Text
jGroupName -> do
            CString
jGroupName' <- Text -> IO CString
textToCString Text
jGroupName
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jGroupName'
    Ptr PageSetup -> Ptr KeyFile -> CString -> IO ()
gtk_page_setup_to_key_file Ptr PageSetup
setup' Ptr KeyFile
keyFile' CString
maybeGroupName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
setup
    KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PageSetupToKeyFileMethodInfo
instance (signature ~ (GLib.KeyFile.KeyFile -> Maybe (T.Text) -> m ()), MonadIO m, IsPageSetup a) => O.MethodInfo PageSetupToKeyFileMethodInfo a signature where
    overloadedMethod = pageSetupToKeyFile

#endif