{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson, Iñaki García Etxebarria and Jonas Platte
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- A GtkPrintSettings object represents the settings of a print dialog in
-- a system-independent way. The main use for this object is that once
-- you’ve printed you can get a settings object that represents the settings
-- the user chose, and the next time you print you can pass that object in so
-- that the user doesn’t have to re-set all his settings.
-- 
-- Its also possible to enumerate the settings so that you can easily save
-- the settings for the next time your app runs, or even store them in a
-- document. The predefined keys try to use shared values as much as possible
-- so that moving such a document between systems still works.
-- 
-- 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.PrintSettings
    ( 

-- * Exported types
    PrintSettings(..)                       ,
    IsPrintSettings                         ,
    toPrintSettings                         ,
    noPrintSettings                         ,


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

#if defined(ENABLE_OVERLOADING)
    ResolvePrintSettingsMethod              ,
#endif


-- ** copy #method:copy#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsCopyMethodInfo             ,
#endif
    printSettingsCopy                       ,


-- ** foreach #method:foreach#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsForeachMethodInfo          ,
#endif
    printSettingsForeach                    ,


-- ** get #method:get#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetMethodInfo              ,
#endif
    printSettingsGet                        ,


-- ** getBool #method:getBool#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetBoolMethodInfo          ,
#endif
    printSettingsGetBool                    ,


-- ** getCollate #method:getCollate#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetCollateMethodInfo       ,
#endif
    printSettingsGetCollate                 ,


-- ** getDefaultSource #method:getDefaultSource#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetDefaultSourceMethodInfo ,
#endif
    printSettingsGetDefaultSource           ,


-- ** getDither #method:getDither#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetDitherMethodInfo        ,
#endif
    printSettingsGetDither                  ,


-- ** getDouble #method:getDouble#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetDoubleMethodInfo        ,
#endif
    printSettingsGetDouble                  ,


-- ** getDoubleWithDefault #method:getDoubleWithDefault#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetDoubleWithDefaultMethodInfo,
#endif
    printSettingsGetDoubleWithDefault       ,


-- ** getDuplex #method:getDuplex#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetDuplexMethodInfo        ,
#endif
    printSettingsGetDuplex                  ,


-- ** getFinishings #method:getFinishings#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetFinishingsMethodInfo    ,
#endif
    printSettingsGetFinishings              ,


-- ** getInt #method:getInt#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetIntMethodInfo           ,
#endif
    printSettingsGetInt                     ,


-- ** getIntWithDefault #method:getIntWithDefault#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetIntWithDefaultMethodInfo,
#endif
    printSettingsGetIntWithDefault          ,


-- ** getLength #method:getLength#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetLengthMethodInfo        ,
#endif
    printSettingsGetLength                  ,


-- ** getMediaType #method:getMediaType#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetMediaTypeMethodInfo     ,
#endif
    printSettingsGetMediaType               ,


-- ** getNCopies #method:getNCopies#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetNCopiesMethodInfo       ,
#endif
    printSettingsGetNCopies                 ,


-- ** getNumberUp #method:getNumberUp#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetNumberUpMethodInfo      ,
#endif
    printSettingsGetNumberUp                ,


-- ** getNumberUpLayout #method:getNumberUpLayout#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetNumberUpLayoutMethodInfo,
#endif
    printSettingsGetNumberUpLayout          ,


-- ** getOrientation #method:getOrientation#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetOrientationMethodInfo   ,
#endif
    printSettingsGetOrientation             ,


-- ** getOutputBin #method:getOutputBin#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetOutputBinMethodInfo     ,
#endif
    printSettingsGetOutputBin               ,


-- ** getPageRanges #method:getPageRanges#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetPageRangesMethodInfo    ,
#endif
    printSettingsGetPageRanges              ,


-- ** getPageSet #method:getPageSet#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetPageSetMethodInfo       ,
#endif
    printSettingsGetPageSet                 ,


-- ** getPaperHeight #method:getPaperHeight#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetPaperHeightMethodInfo   ,
#endif
    printSettingsGetPaperHeight             ,


-- ** getPaperSize #method:getPaperSize#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetPaperSizeMethodInfo     ,
#endif
    printSettingsGetPaperSize               ,


-- ** getPaperWidth #method:getPaperWidth#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetPaperWidthMethodInfo    ,
#endif
    printSettingsGetPaperWidth              ,


-- ** getPrintPages #method:getPrintPages#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetPrintPagesMethodInfo    ,
#endif
    printSettingsGetPrintPages              ,


-- ** getPrinter #method:getPrinter#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetPrinterMethodInfo       ,
#endif
    printSettingsGetPrinter                 ,


-- ** getPrinterLpi #method:getPrinterLpi#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetPrinterLpiMethodInfo    ,
#endif
    printSettingsGetPrinterLpi              ,


-- ** getQuality #method:getQuality#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetQualityMethodInfo       ,
#endif
    printSettingsGetQuality                 ,


-- ** getResolution #method:getResolution#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetResolutionMethodInfo    ,
#endif
    printSettingsGetResolution              ,


-- ** getResolutionX #method:getResolutionX#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetResolutionXMethodInfo   ,
#endif
    printSettingsGetResolutionX             ,


-- ** getResolutionY #method:getResolutionY#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetResolutionYMethodInfo   ,
#endif
    printSettingsGetResolutionY             ,


-- ** getReverse #method:getReverse#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetReverseMethodInfo       ,
#endif
    printSettingsGetReverse                 ,


-- ** getScale #method:getScale#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetScaleMethodInfo         ,
#endif
    printSettingsGetScale                   ,


-- ** getUseColor #method:getUseColor#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsGetUseColorMethodInfo      ,
#endif
    printSettingsGetUseColor                ,


-- ** hasKey #method:hasKey#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsHasKeyMethodInfo           ,
#endif
    printSettingsHasKey                     ,


-- ** loadFile #method:loadFile#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsLoadFileMethodInfo         ,
#endif
    printSettingsLoadFile                   ,


-- ** loadKeyFile #method:loadKeyFile#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsLoadKeyFileMethodInfo      ,
#endif
    printSettingsLoadKeyFile                ,


-- ** new #method:new#

    printSettingsNew                        ,


-- ** newFromFile #method:newFromFile#

    printSettingsNewFromFile                ,


-- ** newFromGvariant #method:newFromGvariant#

    printSettingsNewFromGvariant            ,


-- ** newFromKeyFile #method:newFromKeyFile#

    printSettingsNewFromKeyFile             ,


-- ** set #method:set#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetMethodInfo              ,
#endif
    printSettingsSet                        ,


-- ** setBool #method:setBool#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetBoolMethodInfo          ,
#endif
    printSettingsSetBool                    ,


-- ** setCollate #method:setCollate#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetCollateMethodInfo       ,
#endif
    printSettingsSetCollate                 ,


-- ** setDefaultSource #method:setDefaultSource#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetDefaultSourceMethodInfo ,
#endif
    printSettingsSetDefaultSource           ,


-- ** setDither #method:setDither#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetDitherMethodInfo        ,
#endif
    printSettingsSetDither                  ,


-- ** setDouble #method:setDouble#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetDoubleMethodInfo        ,
#endif
    printSettingsSetDouble                  ,


-- ** setDuplex #method:setDuplex#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetDuplexMethodInfo        ,
#endif
    printSettingsSetDuplex                  ,


-- ** setFinishings #method:setFinishings#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetFinishingsMethodInfo    ,
#endif
    printSettingsSetFinishings              ,


-- ** setInt #method:setInt#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetIntMethodInfo           ,
#endif
    printSettingsSetInt                     ,


-- ** setLength #method:setLength#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetLengthMethodInfo        ,
#endif
    printSettingsSetLength                  ,


-- ** setMediaType #method:setMediaType#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetMediaTypeMethodInfo     ,
#endif
    printSettingsSetMediaType               ,


-- ** setNCopies #method:setNCopies#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetNCopiesMethodInfo       ,
#endif
    printSettingsSetNCopies                 ,


-- ** setNumberUp #method:setNumberUp#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetNumberUpMethodInfo      ,
#endif
    printSettingsSetNumberUp                ,


-- ** setNumberUpLayout #method:setNumberUpLayout#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetNumberUpLayoutMethodInfo,
#endif
    printSettingsSetNumberUpLayout          ,


-- ** setOrientation #method:setOrientation#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetOrientationMethodInfo   ,
#endif
    printSettingsSetOrientation             ,


-- ** setOutputBin #method:setOutputBin#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetOutputBinMethodInfo     ,
#endif
    printSettingsSetOutputBin               ,


-- ** setPageRanges #method:setPageRanges#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetPageRangesMethodInfo    ,
#endif
    printSettingsSetPageRanges              ,


-- ** setPageSet #method:setPageSet#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetPageSetMethodInfo       ,
#endif
    printSettingsSetPageSet                 ,


-- ** setPaperHeight #method:setPaperHeight#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetPaperHeightMethodInfo   ,
#endif
    printSettingsSetPaperHeight             ,


-- ** setPaperSize #method:setPaperSize#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetPaperSizeMethodInfo     ,
#endif
    printSettingsSetPaperSize               ,


-- ** setPaperWidth #method:setPaperWidth#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetPaperWidthMethodInfo    ,
#endif
    printSettingsSetPaperWidth              ,


-- ** setPrintPages #method:setPrintPages#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetPrintPagesMethodInfo    ,
#endif
    printSettingsSetPrintPages              ,


-- ** setPrinter #method:setPrinter#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetPrinterMethodInfo       ,
#endif
    printSettingsSetPrinter                 ,


-- ** setPrinterLpi #method:setPrinterLpi#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetPrinterLpiMethodInfo    ,
#endif
    printSettingsSetPrinterLpi              ,


-- ** setQuality #method:setQuality#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetQualityMethodInfo       ,
#endif
    printSettingsSetQuality                 ,


-- ** setResolution #method:setResolution#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetResolutionMethodInfo    ,
#endif
    printSettingsSetResolution              ,


-- ** setResolutionXy #method:setResolutionXy#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetResolutionXyMethodInfo  ,
#endif
    printSettingsSetResolutionXy            ,


-- ** setReverse #method:setReverse#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetReverseMethodInfo       ,
#endif
    printSettingsSetReverse                 ,


-- ** setScale #method:setScale#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetScaleMethodInfo         ,
#endif
    printSettingsSetScale                   ,


-- ** setUseColor #method:setUseColor#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsSetUseColorMethodInfo      ,
#endif
    printSettingsSetUseColor                ,


-- ** toFile #method:toFile#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsToFileMethodInfo           ,
#endif
    printSettingsToFile                     ,


-- ** toGvariant #method:toGvariant#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsToGvariantMethodInfo       ,
#endif
    printSettingsToGvariant                 ,


-- ** toKeyFile #method:toKeyFile#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsToKeyFileMethodInfo        ,
#endif
    printSettingsToKeyFile                  ,


-- ** unset #method:unset#

#if defined(ENABLE_OVERLOADING)
    PrintSettingsUnsetMethodInfo            ,
#endif
    printSettingsUnset                      ,




    ) 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 qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Structs.PageRange as Gtk.PageRange
import {-# SOURCE #-} qualified GI.Gtk.Structs.PaperSize as Gtk.PaperSize

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

instance GObject PrintSettings where
    gobjectType :: IO GType
gobjectType = IO GType
c_gtk_print_settings_get_type
    

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

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

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

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

-- | A convenience alias for `Nothing` :: `Maybe` `PrintSettings`.
noPrintSettings :: Maybe PrintSettings
noPrintSettings :: Maybe PrintSettings
noPrintSettings = Maybe PrintSettings
forall a. Maybe a
Nothing

#if defined(ENABLE_OVERLOADING)
type family ResolvePrintSettingsMethod (t :: Symbol) (o :: *) :: * where
    ResolvePrintSettingsMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolvePrintSettingsMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolvePrintSettingsMethod "copy" o = PrintSettingsCopyMethodInfo
    ResolvePrintSettingsMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolvePrintSettingsMethod "foreach" o = PrintSettingsForeachMethodInfo
    ResolvePrintSettingsMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolvePrintSettingsMethod "get" o = PrintSettingsGetMethodInfo
    ResolvePrintSettingsMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolvePrintSettingsMethod "hasKey" o = PrintSettingsHasKeyMethodInfo
    ResolvePrintSettingsMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolvePrintSettingsMethod "loadFile" o = PrintSettingsLoadFileMethodInfo
    ResolvePrintSettingsMethod "loadKeyFile" o = PrintSettingsLoadKeyFileMethodInfo
    ResolvePrintSettingsMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolvePrintSettingsMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolvePrintSettingsMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolvePrintSettingsMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolvePrintSettingsMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolvePrintSettingsMethod "set" o = PrintSettingsSetMethodInfo
    ResolvePrintSettingsMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolvePrintSettingsMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolvePrintSettingsMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolvePrintSettingsMethod "toFile" o = PrintSettingsToFileMethodInfo
    ResolvePrintSettingsMethod "toGvariant" o = PrintSettingsToGvariantMethodInfo
    ResolvePrintSettingsMethod "toKeyFile" o = PrintSettingsToKeyFileMethodInfo
    ResolvePrintSettingsMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolvePrintSettingsMethod "unset" o = PrintSettingsUnsetMethodInfo
    ResolvePrintSettingsMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolvePrintSettingsMethod "getBool" o = PrintSettingsGetBoolMethodInfo
    ResolvePrintSettingsMethod "getCollate" o = PrintSettingsGetCollateMethodInfo
    ResolvePrintSettingsMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolvePrintSettingsMethod "getDefaultSource" o = PrintSettingsGetDefaultSourceMethodInfo
    ResolvePrintSettingsMethod "getDither" o = PrintSettingsGetDitherMethodInfo
    ResolvePrintSettingsMethod "getDouble" o = PrintSettingsGetDoubleMethodInfo
    ResolvePrintSettingsMethod "getDoubleWithDefault" o = PrintSettingsGetDoubleWithDefaultMethodInfo
    ResolvePrintSettingsMethod "getDuplex" o = PrintSettingsGetDuplexMethodInfo
    ResolvePrintSettingsMethod "getFinishings" o = PrintSettingsGetFinishingsMethodInfo
    ResolvePrintSettingsMethod "getInt" o = PrintSettingsGetIntMethodInfo
    ResolvePrintSettingsMethod "getIntWithDefault" o = PrintSettingsGetIntWithDefaultMethodInfo
    ResolvePrintSettingsMethod "getLength" o = PrintSettingsGetLengthMethodInfo
    ResolvePrintSettingsMethod "getMediaType" o = PrintSettingsGetMediaTypeMethodInfo
    ResolvePrintSettingsMethod "getNCopies" o = PrintSettingsGetNCopiesMethodInfo
    ResolvePrintSettingsMethod "getNumberUp" o = PrintSettingsGetNumberUpMethodInfo
    ResolvePrintSettingsMethod "getNumberUpLayout" o = PrintSettingsGetNumberUpLayoutMethodInfo
    ResolvePrintSettingsMethod "getOrientation" o = PrintSettingsGetOrientationMethodInfo
    ResolvePrintSettingsMethod "getOutputBin" o = PrintSettingsGetOutputBinMethodInfo
    ResolvePrintSettingsMethod "getPageRanges" o = PrintSettingsGetPageRangesMethodInfo
    ResolvePrintSettingsMethod "getPageSet" o = PrintSettingsGetPageSetMethodInfo
    ResolvePrintSettingsMethod "getPaperHeight" o = PrintSettingsGetPaperHeightMethodInfo
    ResolvePrintSettingsMethod "getPaperSize" o = PrintSettingsGetPaperSizeMethodInfo
    ResolvePrintSettingsMethod "getPaperWidth" o = PrintSettingsGetPaperWidthMethodInfo
    ResolvePrintSettingsMethod "getPrintPages" o = PrintSettingsGetPrintPagesMethodInfo
    ResolvePrintSettingsMethod "getPrinter" o = PrintSettingsGetPrinterMethodInfo
    ResolvePrintSettingsMethod "getPrinterLpi" o = PrintSettingsGetPrinterLpiMethodInfo
    ResolvePrintSettingsMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolvePrintSettingsMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolvePrintSettingsMethod "getQuality" o = PrintSettingsGetQualityMethodInfo
    ResolvePrintSettingsMethod "getResolution" o = PrintSettingsGetResolutionMethodInfo
    ResolvePrintSettingsMethod "getResolutionX" o = PrintSettingsGetResolutionXMethodInfo
    ResolvePrintSettingsMethod "getResolutionY" o = PrintSettingsGetResolutionYMethodInfo
    ResolvePrintSettingsMethod "getReverse" o = PrintSettingsGetReverseMethodInfo
    ResolvePrintSettingsMethod "getScale" o = PrintSettingsGetScaleMethodInfo
    ResolvePrintSettingsMethod "getUseColor" o = PrintSettingsGetUseColorMethodInfo
    ResolvePrintSettingsMethod "setBool" o = PrintSettingsSetBoolMethodInfo
    ResolvePrintSettingsMethod "setCollate" o = PrintSettingsSetCollateMethodInfo
    ResolvePrintSettingsMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolvePrintSettingsMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolvePrintSettingsMethod "setDefaultSource" o = PrintSettingsSetDefaultSourceMethodInfo
    ResolvePrintSettingsMethod "setDither" o = PrintSettingsSetDitherMethodInfo
    ResolvePrintSettingsMethod "setDouble" o = PrintSettingsSetDoubleMethodInfo
    ResolvePrintSettingsMethod "setDuplex" o = PrintSettingsSetDuplexMethodInfo
    ResolvePrintSettingsMethod "setFinishings" o = PrintSettingsSetFinishingsMethodInfo
    ResolvePrintSettingsMethod "setInt" o = PrintSettingsSetIntMethodInfo
    ResolvePrintSettingsMethod "setLength" o = PrintSettingsSetLengthMethodInfo
    ResolvePrintSettingsMethod "setMediaType" o = PrintSettingsSetMediaTypeMethodInfo
    ResolvePrintSettingsMethod "setNCopies" o = PrintSettingsSetNCopiesMethodInfo
    ResolvePrintSettingsMethod "setNumberUp" o = PrintSettingsSetNumberUpMethodInfo
    ResolvePrintSettingsMethod "setNumberUpLayout" o = PrintSettingsSetNumberUpLayoutMethodInfo
    ResolvePrintSettingsMethod "setOrientation" o = PrintSettingsSetOrientationMethodInfo
    ResolvePrintSettingsMethod "setOutputBin" o = PrintSettingsSetOutputBinMethodInfo
    ResolvePrintSettingsMethod "setPageRanges" o = PrintSettingsSetPageRangesMethodInfo
    ResolvePrintSettingsMethod "setPageSet" o = PrintSettingsSetPageSetMethodInfo
    ResolvePrintSettingsMethod "setPaperHeight" o = PrintSettingsSetPaperHeightMethodInfo
    ResolvePrintSettingsMethod "setPaperSize" o = PrintSettingsSetPaperSizeMethodInfo
    ResolvePrintSettingsMethod "setPaperWidth" o = PrintSettingsSetPaperWidthMethodInfo
    ResolvePrintSettingsMethod "setPrintPages" o = PrintSettingsSetPrintPagesMethodInfo
    ResolvePrintSettingsMethod "setPrinter" o = PrintSettingsSetPrinterMethodInfo
    ResolvePrintSettingsMethod "setPrinterLpi" o = PrintSettingsSetPrinterLpiMethodInfo
    ResolvePrintSettingsMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolvePrintSettingsMethod "setQuality" o = PrintSettingsSetQualityMethodInfo
    ResolvePrintSettingsMethod "setResolution" o = PrintSettingsSetResolutionMethodInfo
    ResolvePrintSettingsMethod "setResolutionXy" o = PrintSettingsSetResolutionXyMethodInfo
    ResolvePrintSettingsMethod "setReverse" o = PrintSettingsSetReverseMethodInfo
    ResolvePrintSettingsMethod "setScale" o = PrintSettingsSetScaleMethodInfo
    ResolvePrintSettingsMethod "setUseColor" o = PrintSettingsSetUseColorMethodInfo
    ResolvePrintSettingsMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolvePrintSettingsMethod t PrintSettings, O.MethodInfo info PrintSettings p) => OL.IsLabel t (PrintSettings -> 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 PrintSettings
type instance O.AttributeList PrintSettings = PrintSettingsAttributeList
type PrintSettingsAttributeList = ('[ ] :: [(Symbol, *)])
#endif

#if defined(ENABLE_OVERLOADING)
#endif

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

#endif

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

foreign import ccall "gtk_print_settings_new" gtk_print_settings_new :: 
    IO (Ptr PrintSettings)

-- | Creates a new t'GI.Gtk.Objects.PrintSettings.PrintSettings' object.
-- 
-- /Since: 2.10/
printSettingsNew ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m PrintSettings
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.PrintSettings.PrintSettings' object
printSettingsNew :: m PrintSettings
printSettingsNew  = IO PrintSettings -> m PrintSettings
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintSettings -> m PrintSettings)
-> IO PrintSettings -> m PrintSettings
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
result <- IO (Ptr PrintSettings)
gtk_print_settings_new
    Text -> Ptr PrintSettings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsNew" Ptr PrintSettings
result
    PrintSettings
result' <- ((ManagedPtr PrintSettings -> PrintSettings)
-> Ptr PrintSettings -> IO PrintSettings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PrintSettings -> PrintSettings
PrintSettings) Ptr PrintSettings
result
    PrintSettings -> IO PrintSettings
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PrintSettings::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 settings from"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "PrintSettings" })
-- throws : True
-- Skip return : False

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

-- | Reads the print settings from /@fileName@/. Returns a new t'GI.Gtk.Objects.PrintSettings.PrintSettings'
-- object with the restored settings, or 'P.Nothing' if an error occurred. If the
-- file could not be loaded then error is set to either a t'GI.GLib.Enums.FileError' or
-- t'GI.GLib.Enums.KeyFileError'.  See 'GI.Gtk.Objects.PrintSettings.printSettingsToFile'.
-- 
-- /Since: 2.12/
printSettingsNewFromFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    [Char]
    -- ^ /@fileName@/: the filename to read the settings from
    -> m PrintSettings
    -- ^ __Returns:__ the restored t'GI.Gtk.Objects.PrintSettings.PrintSettings' /(Can throw 'Data.GI.Base.GError.GError')/
printSettingsNewFromFile :: [Char] -> m PrintSettings
printSettingsNewFromFile fileName :: [Char]
fileName = IO PrintSettings -> m PrintSettings
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintSettings -> m PrintSettings)
-> IO PrintSettings -> m PrintSettings
forall a b. (a -> b) -> a -> b
$ do
    CString
fileName' <- [Char] -> IO CString
stringToCString [Char]
fileName
    IO PrintSettings -> IO () -> IO PrintSettings
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr PrintSettings
result <- (Ptr (Ptr GError) -> IO (Ptr PrintSettings))
-> IO (Ptr PrintSettings)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr PrintSettings))
 -> IO (Ptr PrintSettings))
-> (Ptr (Ptr GError) -> IO (Ptr PrintSettings))
-> IO (Ptr PrintSettings)
forall a b. (a -> b) -> a -> b
$ CString -> Ptr (Ptr GError) -> IO (Ptr PrintSettings)
gtk_print_settings_new_from_file CString
fileName'
        Text -> Ptr PrintSettings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsNewFromFile" Ptr PrintSettings
result
        PrintSettings
result' <- ((ManagedPtr PrintSettings -> PrintSettings)
-> Ptr PrintSettings -> IO PrintSettings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PrintSettings -> PrintSettings
PrintSettings) Ptr PrintSettings
result
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fileName'
        PrintSettings -> IO PrintSettings
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
fileName'
     )

#if defined(ENABLE_OVERLOADING)
#endif

-- method PrintSettings::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 = "PrintSettings" })
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_new_from_gvariant" gtk_print_settings_new_from_gvariant :: 
    Ptr GVariant ->                         -- variant : TVariant
    IO (Ptr PrintSettings)

-- | Deserialize print settings from an a{sv} variant in
-- the format produced by 'GI.Gtk.Objects.PrintSettings.printSettingsToGvariant'.
-- 
-- /Since: 3.22/
printSettingsNewFromGvariant ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GVariant
    -- ^ /@variant@/: an a{sv} t'GVariant'
    -> m PrintSettings
    -- ^ __Returns:__ a new t'GI.Gtk.Objects.PrintSettings.PrintSettings' object
printSettingsNewFromGvariant :: GVariant -> m PrintSettings
printSettingsNewFromGvariant variant :: GVariant
variant = IO PrintSettings -> m PrintSettings
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintSettings -> m PrintSettings)
-> IO PrintSettings -> m PrintSettings
forall a b. (a -> b) -> a -> b
$ do
    Ptr GVariant
variant' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
variant
    Ptr PrintSettings
result <- Ptr GVariant -> IO (Ptr PrintSettings)
gtk_print_settings_new_from_gvariant Ptr GVariant
variant'
    Text -> Ptr PrintSettings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsNewFromGvariant" Ptr PrintSettings
result
    PrintSettings
result' <- ((ManagedPtr PrintSettings -> PrintSettings)
-> Ptr PrintSettings -> IO PrintSettings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PrintSettings -> PrintSettings
PrintSettings) Ptr PrintSettings
result
    GVariant -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr GVariant
variant
    PrintSettings -> IO PrintSettings
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result'

#if defined(ENABLE_OVERLOADING)
#endif

-- method PrintSettings::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 settings 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 to use, or %NULL to use\n    the default \8220Print Settings\8221"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just
--               (TInterface Name { namespace = "Gtk" , name = "PrintSettings" })
-- throws : True
-- Skip return : False

foreign import ccall "gtk_print_settings_new_from_key_file" gtk_print_settings_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 PrintSettings)

-- | Reads the print settings from the group /@groupName@/ in /@keyFile@/.  Returns a
-- new t'GI.Gtk.Objects.PrintSettings.PrintSettings' object with the restored settings, or 'P.Nothing' if an
-- error occurred. If the file could not be loaded then error is set to either
-- a t'GI.GLib.Enums.FileError' or t'GI.GLib.Enums.KeyFileError'.
-- 
-- /Since: 2.12/
printSettingsNewFromKeyFile ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    GLib.KeyFile.KeyFile
    -- ^ /@keyFile@/: the t'GI.GLib.Structs.KeyFile.KeyFile' to retrieve the settings from
    -> Maybe (T.Text)
    -- ^ /@groupName@/: the name of the group to use, or 'P.Nothing' to use
    --     the default “Print Settings”
    -> m PrintSettings
    -- ^ __Returns:__ the restored t'GI.Gtk.Objects.PrintSettings.PrintSettings' /(Can throw 'Data.GI.Base.GError.GError')/
printSettingsNewFromKeyFile :: KeyFile -> Maybe Text -> m PrintSettings
printSettingsNewFromKeyFile keyFile :: KeyFile
keyFile groupName :: Maybe Text
groupName = IO PrintSettings -> m PrintSettings
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintSettings -> m PrintSettings)
-> IO PrintSettings -> m PrintSettings
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 PrintSettings -> IO () -> IO PrintSettings
forall a b. IO a -> IO b -> IO a
onException (do
        Ptr PrintSettings
result <- (Ptr (Ptr GError) -> IO (Ptr PrintSettings))
-> IO (Ptr PrintSettings)
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO (Ptr PrintSettings))
 -> IO (Ptr PrintSettings))
-> (Ptr (Ptr GError) -> IO (Ptr PrintSettings))
-> IO (Ptr PrintSettings)
forall a b. (a -> b) -> a -> b
$ Ptr KeyFile
-> CString -> Ptr (Ptr GError) -> IO (Ptr PrintSettings)
gtk_print_settings_new_from_key_file Ptr KeyFile
keyFile' CString
maybeGroupName
        Text -> Ptr PrintSettings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsNewFromKeyFile" Ptr PrintSettings
result
        PrintSettings
result' <- ((ManagedPtr PrintSettings -> PrintSettings)
-> Ptr PrintSettings -> IO PrintSettings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PrintSettings -> PrintSettings
PrintSettings) Ptr PrintSettings
result
        KeyFile -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr KeyFile
keyFile
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
        PrintSettings -> IO PrintSettings
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result'
     ) (do
        CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeGroupName
     )

#if defined(ENABLE_OVERLOADING)
#endif

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

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

-- | Copies a t'GI.Gtk.Objects.PrintSettings.PrintSettings' object.
-- 
-- /Since: 2.10/
printSettingsCopy ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@other@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m PrintSettings
    -- ^ __Returns:__ a newly allocated copy of /@other@/
printSettingsCopy :: a -> m PrintSettings
printSettingsCopy other :: a
other = IO PrintSettings -> m PrintSettings
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintSettings -> m PrintSettings)
-> IO PrintSettings -> m PrintSettings
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
other' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
other
    Ptr PrintSettings
result <- Ptr PrintSettings -> IO (Ptr PrintSettings)
gtk_print_settings_copy Ptr PrintSettings
other'
    Text -> Ptr PrintSettings -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsCopy" Ptr PrintSettings
result
    PrintSettings
result' <- ((ManagedPtr PrintSettings -> PrintSettings)
-> Ptr PrintSettings -> IO PrintSettings
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
wrapObject ManagedPtr PrintSettings -> PrintSettings
PrintSettings) Ptr PrintSettings
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
other
    PrintSettings -> IO PrintSettings
forall (m :: * -> *) a. Monad m => a -> m a
return PrintSettings
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsCopyMethodInfo
instance (signature ~ (m PrintSettings), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsCopyMethodInfo a signature where
    overloadedMethod = printSettingsCopy

#endif

-- method PrintSettings::foreach
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "func"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettingsFunc" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the function to call"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeCall
--           , argClosure = 2
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "user_data"
--           , argType = TBasicType TPtr
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "user data for @func"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_foreach" gtk_print_settings_foreach :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    FunPtr Gtk.Callbacks.C_PrintSettingsFunc -> -- func : TInterface (Name {namespace = "Gtk", name = "PrintSettingsFunc"})
    Ptr () ->                               -- user_data : TBasicType TPtr
    IO ()

-- | Calls /@func@/ for each key-value pair of /@settings@/.
-- 
-- /Since: 2.10/
printSettingsForeach ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.Callbacks.PrintSettingsFunc
    -- ^ /@func@/: the function to call
    -> m ()
printSettingsForeach :: a -> PrintSettingsFunc -> m ()
printSettingsForeach settings :: a
settings func :: PrintSettingsFunc
func = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    FunPtr C_PrintSettingsFunc
func' <- C_PrintSettingsFunc -> IO (FunPtr C_PrintSettingsFunc)
Gtk.Callbacks.mk_PrintSettingsFunc (Maybe (Ptr (FunPtr C_PrintSettingsFunc))
-> PrintSettingsFunc_WithClosures -> C_PrintSettingsFunc
Gtk.Callbacks.wrap_PrintSettingsFunc Maybe (Ptr (FunPtr C_PrintSettingsFunc))
forall a. Maybe a
Nothing (PrintSettingsFunc -> PrintSettingsFunc_WithClosures
Gtk.Callbacks.drop_closures_PrintSettingsFunc PrintSettingsFunc
func))
    let userData :: Ptr a
userData = Ptr a
forall a. Ptr a
nullPtr
    Ptr PrintSettings -> FunPtr C_PrintSettingsFunc -> Ptr () -> IO ()
gtk_print_settings_foreach Ptr PrintSettings
settings' FunPtr C_PrintSettingsFunc
func' Ptr ()
forall a. Ptr a
userData
    Ptr Any -> IO ()
forall a. Ptr a -> IO ()
safeFreeFunPtr (Ptr Any -> IO ()) -> Ptr Any -> IO ()
forall a b. (a -> b) -> a -> b
$ FunPtr C_PrintSettingsFunc -> Ptr Any
forall a b. FunPtr a -> Ptr b
castFunPtrToPtr FunPtr C_PrintSettingsFunc
func'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsForeachMethodInfo
instance (signature ~ (Gtk.Callbacks.PrintSettingsFunc -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsForeachMethodInfo a signature where
    overloadedMethod = printSettingsForeach

#endif

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

foreign import ccall "gtk_print_settings_get" gtk_print_settings_get :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    IO CString

-- | Looks up the string value associated with /@key@/.
-- 
-- /Since: 2.10/
printSettingsGet ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> m T.Text
    -- ^ __Returns:__ the string value for /@key@/
printSettingsGet :: a -> Text -> m Text
printSettingsGet settings :: a
settings key :: Text
key = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
result <- Ptr PrintSettings -> CString -> IO CString
gtk_print_settings_get Ptr PrintSettings
settings' CString
key'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsGet" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetMethodInfo
instance (signature ~ (T.Text -> m T.Text), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetMethodInfo a signature where
    overloadedMethod = printSettingsGet

#endif

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

foreign import ccall "gtk_print_settings_get_bool" gtk_print_settings_get_bool :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    IO CInt

-- | Returns the boolean represented by the value
-- that is associated with /@key@/.
-- 
-- The string “true” represents 'P.True', any other
-- string 'P.False'.
-- 
-- /Since: 2.10/
printSettingsGetBool ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> m Bool
    -- ^ __Returns:__ 'P.True', if /@key@/ maps to a true value.
printSettingsGetBool :: a -> Text -> m Bool
printSettingsGetBool settings :: a
settings key :: Text
key = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    CInt
result <- Ptr PrintSettings -> CString -> IO CInt
gtk_print_settings_get_bool Ptr PrintSettings
settings' CString
key'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetBoolMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetBoolMethodInfo a signature where
    overloadedMethod = printSettingsGetBool

#endif

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

foreign import ccall "gtk_print_settings_get_collate" gtk_print_settings_get_collate :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CInt

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_COLLATE'.
-- 
-- /Since: 2.10/
printSettingsGetCollate ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Bool
    -- ^ __Returns:__ whether to collate the printed pages
printSettingsGetCollate :: a -> m Bool
printSettingsGetCollate settings :: a
settings = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CInt
result <- Ptr PrintSettings -> IO CInt
gtk_print_settings_get_collate Ptr PrintSettings
settings'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetCollateMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetCollateMethodInfo a signature where
    overloadedMethod = printSettingsGetCollate

#endif

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

foreign import ccall "gtk_print_settings_get_default_source" gtk_print_settings_get_default_source :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CString

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_DEFAULT_SOURCE'.
-- 
-- /Since: 2.10/
printSettingsGetDefaultSource ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m T.Text
    -- ^ __Returns:__ the default source
printSettingsGetDefaultSource :: a -> m Text
printSettingsGetDefaultSource settings :: a
settings = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
result <- Ptr PrintSettings -> IO CString
gtk_print_settings_get_default_source Ptr PrintSettings
settings'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsGetDefaultSource" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetDefaultSourceMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetDefaultSourceMethodInfo a signature where
    overloadedMethod = printSettingsGetDefaultSource

#endif

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

foreign import ccall "gtk_print_settings_get_dither" gtk_print_settings_get_dither :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CString

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_DITHER'.
-- 
-- /Since: 2.10/
printSettingsGetDither ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m T.Text
    -- ^ __Returns:__ the dithering that is used
printSettingsGetDither :: a -> m Text
printSettingsGetDither settings :: a
settings = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
result <- Ptr PrintSettings -> IO CString
gtk_print_settings_get_dither Ptr PrintSettings
settings'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsGetDither" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetDitherMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetDitherMethodInfo a signature where
    overloadedMethod = printSettingsGetDither

#endif

-- method PrintSettings::get_double
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , 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_print_settings_get_double" gtk_print_settings_get_double :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    IO CDouble

-- | Returns the double value associated with /@key@/, or 0.
-- 
-- /Since: 2.10/
printSettingsGetDouble ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> m Double
    -- ^ __Returns:__ the double value of /@key@/
printSettingsGetDouble :: a -> Text -> m Double
printSettingsGetDouble settings :: a
settings key :: Text
key = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    CDouble
result <- Ptr PrintSettings -> CString -> IO CDouble
gtk_print_settings_get_double Ptr PrintSettings
settings' CString
key'
    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
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetDoubleMethodInfo
instance (signature ~ (T.Text -> m Double), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetDoubleMethodInfo a signature where
    overloadedMethod = printSettingsGetDouble

#endif

-- method PrintSettings::get_double_with_default
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "def"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the default 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_print_settings_get_double_with_default" gtk_print_settings_get_double_with_default :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    CDouble ->                              -- def : TBasicType TDouble
    IO CDouble

-- | Returns the floating point number represented by
-- the value that is associated with /@key@/, or /@defaultVal@/
-- if the value does not represent a floating point number.
-- 
-- Floating point numbers are parsed with 'GI.GLib.Functions.asciiStrtod'.
-- 
-- /Since: 2.10/
printSettingsGetDoubleWithDefault ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> Double
    -- ^ /@def@/: the default value
    -> m Double
    -- ^ __Returns:__ the floating point number associated with /@key@/
printSettingsGetDoubleWithDefault :: a -> Text -> Double -> m Double
printSettingsGetDoubleWithDefault settings :: a
settings key :: Text
key def :: Double
def = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    let def' :: CDouble
def' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
def
    CDouble
result <- Ptr PrintSettings -> CString -> CDouble -> IO CDouble
gtk_print_settings_get_double_with_default Ptr PrintSettings
settings' CString
key' CDouble
def'
    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
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetDoubleWithDefaultMethodInfo
instance (signature ~ (T.Text -> Double -> m Double), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetDoubleWithDefaultMethodInfo a signature where
    overloadedMethod = printSettingsGetDoubleWithDefault

#endif

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

foreign import ccall "gtk_print_settings_get_duplex" gtk_print_settings_get_duplex :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CUInt

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_DUPLEX'.
-- 
-- /Since: 2.10/
printSettingsGetDuplex ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Gtk.Enums.PrintDuplex
    -- ^ __Returns:__ whether to print the output in duplex.
printSettingsGetDuplex :: a -> m PrintDuplex
printSettingsGetDuplex settings :: a
settings = IO PrintDuplex -> m PrintDuplex
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintDuplex -> m PrintDuplex)
-> IO PrintDuplex -> m PrintDuplex
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CUInt
result <- Ptr PrintSettings -> IO CUInt
gtk_print_settings_get_duplex Ptr PrintSettings
settings'
    let result' :: PrintDuplex
result' = (Int -> PrintDuplex
forall a. Enum a => Int -> a
toEnum (Int -> PrintDuplex) -> (CUInt -> Int) -> CUInt -> PrintDuplex
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
settings
    PrintDuplex -> IO PrintDuplex
forall (m :: * -> *) a. Monad m => a -> m a
return PrintDuplex
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetDuplexMethodInfo
instance (signature ~ (m Gtk.Enums.PrintDuplex), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetDuplexMethodInfo a signature where
    overloadedMethod = printSettingsGetDuplex

#endif

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

foreign import ccall "gtk_print_settings_get_finishings" gtk_print_settings_get_finishings :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CString

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_FINISHINGS'.
-- 
-- /Since: 2.10/
printSettingsGetFinishings ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m T.Text
    -- ^ __Returns:__ the finishings
printSettingsGetFinishings :: a -> m Text
printSettingsGetFinishings settings :: a
settings = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
result <- Ptr PrintSettings -> IO CString
gtk_print_settings_get_finishings Ptr PrintSettings
settings'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsGetFinishings" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetFinishingsMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetFinishingsMethodInfo a signature where
    overloadedMethod = printSettingsGetFinishings

#endif

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

foreign import ccall "gtk_print_settings_get_int" gtk_print_settings_get_int :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    IO Int32

-- | Returns the integer value of /@key@/, or 0.
-- 
-- /Since: 2.10/
printSettingsGetInt ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> m Int32
    -- ^ __Returns:__ the integer value of /@key@/
printSettingsGetInt :: a -> Text -> m Int32
printSettingsGetInt settings :: a
settings key :: Text
key = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    Int32
result <- Ptr PrintSettings -> CString -> IO Int32
gtk_print_settings_get_int Ptr PrintSettings
settings' CString
key'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetIntMethodInfo
instance (signature ~ (T.Text -> m Int32), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetIntMethodInfo a signature where
    overloadedMethod = printSettingsGetInt

#endif

-- method PrintSettings::get_int_with_default
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "def"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the default value" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TInt)
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_get_int_with_default" gtk_print_settings_get_int_with_default :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    Int32 ->                                -- def : TBasicType TInt
    IO Int32

-- | Returns the value of /@key@/, interpreted as
-- an integer, or the default value.
-- 
-- /Since: 2.10/
printSettingsGetIntWithDefault ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> Int32
    -- ^ /@def@/: the default value
    -> m Int32
    -- ^ __Returns:__ the integer value of /@key@/
printSettingsGetIntWithDefault :: a -> Text -> Int32 -> m Int32
printSettingsGetIntWithDefault settings :: a
settings key :: Text
key def :: Int32
def = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    Int32
result <- Ptr PrintSettings -> CString -> Int32 -> IO Int32
gtk_print_settings_get_int_with_default Ptr PrintSettings
settings' CString
key' Int32
def
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetIntWithDefaultMethodInfo
instance (signature ~ (T.Text -> Int32 -> m Int32), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetIntWithDefaultMethodInfo a signature where
    overloadedMethod = printSettingsGetIntWithDefault

#endif

-- method PrintSettings::get_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , 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 of 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_print_settings_get_length" gtk_print_settings_get_length :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Returns the value associated with /@key@/, interpreted
-- as a length. The returned value is converted to /@units@/.
-- 
-- /Since: 2.10/
printSettingsGetLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit of the return value
    -> m Double
    -- ^ __Returns:__ the length value of /@key@/, converted to /@unit@/
printSettingsGetLength :: a -> Text -> Unit -> m Double
printSettingsGetLength settings :: a
settings key :: Text
key 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    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 PrintSettings -> CString -> CUInt -> IO CDouble
gtk_print_settings_get_length Ptr PrintSettings
settings' CString
key' 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
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetLengthMethodInfo
instance (signature ~ (T.Text -> Gtk.Enums.Unit -> m Double), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetLengthMethodInfo a signature where
    overloadedMethod = printSettingsGetLength

#endif

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

foreign import ccall "gtk_print_settings_get_media_type" gtk_print_settings_get_media_type :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CString

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_MEDIA_TYPE'.
-- 
-- The set of media types is defined in PWG 5101.1-2002 PWG.
-- 
-- /Since: 2.10/
printSettingsGetMediaType ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m T.Text
    -- ^ __Returns:__ the media type
printSettingsGetMediaType :: a -> m Text
printSettingsGetMediaType settings :: a
settings = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
result <- Ptr PrintSettings -> IO CString
gtk_print_settings_get_media_type Ptr PrintSettings
settings'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsGetMediaType" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetMediaTypeMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetMediaTypeMethodInfo a signature where
    overloadedMethod = printSettingsGetMediaType

#endif

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

foreign import ccall "gtk_print_settings_get_n_copies" gtk_print_settings_get_n_copies :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO Int32

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_N_COPIES'.
-- 
-- /Since: 2.10/
printSettingsGetNCopies ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Int32
    -- ^ __Returns:__ the number of copies to print
printSettingsGetNCopies :: a -> m Int32
printSettingsGetNCopies settings :: a
settings = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Int32
result <- Ptr PrintSettings -> IO Int32
gtk_print_settings_get_n_copies Ptr PrintSettings
settings'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetNCopiesMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetNCopiesMethodInfo a signature where
    overloadedMethod = printSettingsGetNCopies

#endif

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

foreign import ccall "gtk_print_settings_get_number_up" gtk_print_settings_get_number_up :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO Int32

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_NUMBER_UP'.
-- 
-- /Since: 2.10/
printSettingsGetNumberUp ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Int32
    -- ^ __Returns:__ the number of pages per sheet
printSettingsGetNumberUp :: a -> m Int32
printSettingsGetNumberUp settings :: a
settings = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Int32
result <- Ptr PrintSettings -> IO Int32
gtk_print_settings_get_number_up Ptr PrintSettings
settings'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetNumberUpMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetNumberUpMethodInfo a signature where
    overloadedMethod = printSettingsGetNumberUp

#endif

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

foreign import ccall "gtk_print_settings_get_number_up_layout" gtk_print_settings_get_number_up_layout :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CUInt

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_NUMBER_UP_LAYOUT'.
-- 
-- /Since: 2.14/
printSettingsGetNumberUpLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Gtk.Enums.NumberUpLayout
    -- ^ __Returns:__ layout of page in number-up mode
printSettingsGetNumberUpLayout :: a -> m NumberUpLayout
printSettingsGetNumberUpLayout settings :: a
settings = IO NumberUpLayout -> m NumberUpLayout
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO NumberUpLayout -> m NumberUpLayout)
-> IO NumberUpLayout -> m NumberUpLayout
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CUInt
result <- Ptr PrintSettings -> IO CUInt
gtk_print_settings_get_number_up_layout Ptr PrintSettings
settings'
    let result' :: NumberUpLayout
result' = (Int -> NumberUpLayout
forall a. Enum a => Int -> a
toEnum (Int -> NumberUpLayout)
-> (CUInt -> Int) -> CUInt -> NumberUpLayout
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
settings
    NumberUpLayout -> IO NumberUpLayout
forall (m :: * -> *) a. Monad m => a -> m a
return NumberUpLayout
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetNumberUpLayoutMethodInfo
instance (signature ~ (m Gtk.Enums.NumberUpLayout), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetNumberUpLayoutMethodInfo a signature where
    overloadedMethod = printSettingsGetNumberUpLayout

#endif

-- method PrintSettings::get_orientation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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_print_settings_get_orientation" gtk_print_settings_get_orientation :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CUInt

-- | Get the value of 'GI.Gtk.Constants.PRINT_SETTINGS_ORIENTATION',
-- converted to a t'GI.Gtk.Enums.PageOrientation'.
-- 
-- /Since: 2.10/
printSettingsGetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Gtk.Enums.PageOrientation
    -- ^ __Returns:__ the orientation
printSettingsGetOrientation :: a -> m PageOrientation
printSettingsGetOrientation settings :: a
settings = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CUInt
result <- Ptr PrintSettings -> IO CUInt
gtk_print_settings_get_orientation Ptr PrintSettings
settings'
    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
settings
    PageOrientation -> IO PageOrientation
forall (m :: * -> *) a. Monad m => a -> m a
return PageOrientation
result'

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

#endif

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

foreign import ccall "gtk_print_settings_get_output_bin" gtk_print_settings_get_output_bin :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CString

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_OUTPUT_BIN'.
-- 
-- /Since: 2.10/
printSettingsGetOutputBin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m T.Text
    -- ^ __Returns:__ the output bin
printSettingsGetOutputBin :: a -> m Text
printSettingsGetOutputBin settings :: a
settings = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
result <- Ptr PrintSettings -> IO CString
gtk_print_settings_get_output_bin Ptr PrintSettings
settings'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsGetOutputBin" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetOutputBinMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetOutputBinMethodInfo a signature where
    overloadedMethod = printSettingsGetOutputBin

#endif

-- method PrintSettings::get_page_ranges
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_ranges"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the length of the returned array"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "num_ranges"
--              , argType = TBasicType TInt
--              , direction = DirectionOut
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText =
--                        Just "return location for the length of the returned array"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferEverything
--              }
--          ]
-- returnType: Just
--               (TCArray
--                  False
--                  (-1)
--                  1
--                  (TInterface Name { namespace = "Gtk" , name = "PageRange" }))
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_get_page_ranges" gtk_print_settings_get_page_ranges :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    Ptr Int32 ->                            -- num_ranges : TBasicType TInt
    IO (Ptr Gtk.PageRange.PageRange)

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAGE_RANGES'.
-- 
-- /Since: 2.10/
printSettingsGetPageRanges ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m [Gtk.PageRange.PageRange]
    -- ^ __Returns:__ an array
    --     of @/GtkPageRanges/@.  Use 'GI.GLib.Functions.free' to free the array when
    --     it is no longer needed.
printSettingsGetPageRanges :: a -> m [PageRange]
printSettingsGetPageRanges settings :: a
settings = IO [PageRange] -> m [PageRange]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [PageRange] -> m [PageRange])
-> IO [PageRange] -> m [PageRange]
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Ptr Int32
numRanges <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr PageRange
result <- Ptr PrintSettings -> Ptr Int32 -> IO (Ptr PageRange)
gtk_print_settings_get_page_ranges Ptr PrintSettings
settings' Ptr Int32
numRanges
    Int32
numRanges' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
numRanges
    Text -> Ptr PageRange -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsGetPageRanges" Ptr PageRange
result
    [Ptr PageRange]
result' <- (Int -> Int32 -> Ptr PageRange -> IO [Ptr PageRange]
forall a b. Integral a => Int -> a -> Ptr b -> IO [Ptr b]
unpackBlockArrayWithLength 8 Int32
numRanges') Ptr PageRange
result
    [PageRange]
result'' <- (Ptr PageRange -> IO PageRange)
-> [Ptr PageRange] -> IO [PageRange]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((ManagedPtr PageRange -> PageRange)
-> Ptr PageRange -> IO PageRange
forall a.
(HasCallStack, WrappedPtr a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapPtr ManagedPtr PageRange -> PageRange
Gtk.PageRange.PageRange) [Ptr PageRange]
result'
    Ptr PageRange -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr PageRange
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
numRanges
    [PageRange] -> IO [PageRange]
forall (m :: * -> *) a. Monad m => a -> m a
return [PageRange]
result''

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetPageRangesMethodInfo
instance (signature ~ (m [Gtk.PageRange.PageRange]), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetPageRangesMethodInfo a signature where
    overloadedMethod = printSettingsGetPageRanges

#endif

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

foreign import ccall "gtk_print_settings_get_page_set" gtk_print_settings_get_page_set :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CUInt

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAGE_SET'.
-- 
-- /Since: 2.10/
printSettingsGetPageSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Gtk.Enums.PageSet
    -- ^ __Returns:__ the set of pages to print
printSettingsGetPageSet :: a -> m PageSet
printSettingsGetPageSet settings :: a
settings = IO PageSet -> m PageSet
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PageSet -> m PageSet) -> IO PageSet -> m PageSet
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CUInt
result <- Ptr PrintSettings -> IO CUInt
gtk_print_settings_get_page_set Ptr PrintSettings
settings'
    let result' :: PageSet
result' = (Int -> PageSet
forall a. Enum a => Int -> a
toEnum (Int -> PageSet) -> (CUInt -> Int) -> CUInt -> PageSet
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
settings
    PageSet -> IO PageSet
forall (m :: * -> *) a. Monad m => a -> m a
return PageSet
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetPageSetMethodInfo
instance (signature ~ (m Gtk.Enums.PageSet), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetPageSetMethodInfo a signature where
    overloadedMethod = printSettingsGetPageSet

#endif

-- method PrintSettings::get_paper_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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_print_settings_get_paper_height" gtk_print_settings_get_paper_height :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAPER_HEIGHT',
-- converted to /@unit@/.
-- 
-- /Since: 2.10/
printSettingsGetPaperHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the paper height, in units of /@unit@/
printSettingsGetPaperHeight :: a -> Unit -> m Double
printSettingsGetPaperHeight settings :: a
settings 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    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 PrintSettings -> CUInt -> IO CDouble
gtk_print_settings_get_paper_height Ptr PrintSettings
settings' 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
settings
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

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

#endif

-- method PrintSettings::get_paper_size
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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_print_settings_get_paper_size" gtk_print_settings_get_paper_size :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO (Ptr Gtk.PaperSize.PaperSize)

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAPER_FORMAT',
-- converted to a t'GI.Gtk.Structs.PaperSize.PaperSize'.
-- 
-- /Since: 2.10/
printSettingsGetPaperSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Gtk.PaperSize.PaperSize
    -- ^ __Returns:__ the paper size
printSettingsGetPaperSize :: a -> m PaperSize
printSettingsGetPaperSize settings :: a
settings = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Ptr PaperSize
result <- Ptr PrintSettings -> IO (Ptr PaperSize)
gtk_print_settings_get_paper_size Ptr PrintSettings
settings'
    Text -> Ptr PaperSize -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsGetPaperSize" Ptr PaperSize
result
    PaperSize
result' <- ((ManagedPtr PaperSize -> PaperSize)
-> Ptr PaperSize -> IO PaperSize
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed ManagedPtr PaperSize -> PaperSize
Gtk.PaperSize.PaperSize) Ptr PaperSize
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    PaperSize -> IO PaperSize
forall (m :: * -> *) a. Monad m => a -> m a
return PaperSize
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetPaperSizeMethodInfo
instance (signature ~ (m Gtk.PaperSize.PaperSize), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetPaperSizeMethodInfo a signature where
    overloadedMethod = printSettingsGetPaperSize

#endif

-- method PrintSettings::get_paper_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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_print_settings_get_paper_width" gtk_print_settings_get_paper_width :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO CDouble

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAPER_WIDTH',
-- converted to /@unit@/.
-- 
-- /Since: 2.10/
printSettingsGetPaperWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit for the return value
    -> m Double
    -- ^ __Returns:__ the paper width, in units of /@unit@/
printSettingsGetPaperWidth :: a -> Unit -> m Double
printSettingsGetPaperWidth settings :: a
settings 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    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 PrintSettings -> CUInt -> IO CDouble
gtk_print_settings_get_paper_width Ptr PrintSettings
settings' 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
settings
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

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

#endif

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

foreign import ccall "gtk_print_settings_get_print_pages" gtk_print_settings_get_print_pages :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CUInt

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PRINT_PAGES'.
-- 
-- /Since: 2.10/
printSettingsGetPrintPages ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Gtk.Enums.PrintPages
    -- ^ __Returns:__ which pages to print
printSettingsGetPrintPages :: a -> m PrintPages
printSettingsGetPrintPages settings :: a
settings = IO PrintPages -> m PrintPages
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintPages -> m PrintPages) -> IO PrintPages -> m PrintPages
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CUInt
result <- Ptr PrintSettings -> IO CUInt
gtk_print_settings_get_print_pages Ptr PrintSettings
settings'
    let result' :: PrintPages
result' = (Int -> PrintPages
forall a. Enum a => Int -> a
toEnum (Int -> PrintPages) -> (CUInt -> Int) -> CUInt -> PrintPages
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
settings
    PrintPages -> IO PrintPages
forall (m :: * -> *) a. Monad m => a -> m a
return PrintPages
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetPrintPagesMethodInfo
instance (signature ~ (m Gtk.Enums.PrintPages), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetPrintPagesMethodInfo a signature where
    overloadedMethod = printSettingsGetPrintPages

#endif

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

foreign import ccall "gtk_print_settings_get_printer" gtk_print_settings_get_printer :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CString

-- | Convenience function to obtain the value of
-- 'GI.Gtk.Constants.PRINT_SETTINGS_PRINTER'.
-- 
-- /Since: 2.10/
printSettingsGetPrinter ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m T.Text
    -- ^ __Returns:__ the printer name
printSettingsGetPrinter :: a -> m Text
printSettingsGetPrinter settings :: a
settings = IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
result <- Ptr PrintSettings -> IO CString
gtk_print_settings_get_printer Ptr PrintSettings
settings'
    Text -> CString -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsGetPrinter" CString
result
    Text
result' <- HasCallStack => CString -> IO Text
CString -> IO Text
cstringToText CString
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Text -> IO Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetPrinterMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetPrinterMethodInfo a signature where
    overloadedMethod = printSettingsGetPrinter

#endif

-- method PrintSettings::get_printer_lpi
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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_print_settings_get_printer_lpi" gtk_print_settings_get_printer_lpi :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CDouble

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PRINTER_LPI'.
-- 
-- /Since: 2.16/
printSettingsGetPrinterLpi ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Double
    -- ^ __Returns:__ the resolution in lpi (lines per inch)
printSettingsGetPrinterLpi :: a -> m Double
printSettingsGetPrinterLpi settings :: a
settings = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CDouble
result <- Ptr PrintSettings -> IO CDouble
gtk_print_settings_get_printer_lpi Ptr PrintSettings
settings'
    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
settings
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetPrinterLpiMethodInfo
instance (signature ~ (m Double), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetPrinterLpiMethodInfo a signature where
    overloadedMethod = printSettingsGetPrinterLpi

#endif

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

foreign import ccall "gtk_print_settings_get_quality" gtk_print_settings_get_quality :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CUInt

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_QUALITY'.
-- 
-- /Since: 2.10/
printSettingsGetQuality ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Gtk.Enums.PrintQuality
    -- ^ __Returns:__ the print quality
printSettingsGetQuality :: a -> m PrintQuality
printSettingsGetQuality settings :: a
settings = IO PrintQuality -> m PrintQuality
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintQuality -> m PrintQuality)
-> IO PrintQuality -> m PrintQuality
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CUInt
result <- Ptr PrintSettings -> IO CUInt
gtk_print_settings_get_quality Ptr PrintSettings
settings'
    let result' :: PrintQuality
result' = (Int -> PrintQuality
forall a. Enum a => Int -> a
toEnum (Int -> PrintQuality) -> (CUInt -> Int) -> CUInt -> PrintQuality
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
settings
    PrintQuality -> IO PrintQuality
forall (m :: * -> *) a. Monad m => a -> m a
return PrintQuality
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetQualityMethodInfo
instance (signature ~ (m Gtk.Enums.PrintQuality), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetQualityMethodInfo a signature where
    overloadedMethod = printSettingsGetQuality

#endif

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

foreign import ccall "gtk_print_settings_get_resolution" gtk_print_settings_get_resolution :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO Int32

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_RESOLUTION'.
-- 
-- /Since: 2.10/
printSettingsGetResolution ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Int32
    -- ^ __Returns:__ the resolution in dpi
printSettingsGetResolution :: a -> m Int32
printSettingsGetResolution settings :: a
settings = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Int32
result <- Ptr PrintSettings -> IO Int32
gtk_print_settings_get_resolution Ptr PrintSettings
settings'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetResolutionMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetResolutionMethodInfo a signature where
    overloadedMethod = printSettingsGetResolution

#endif

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

foreign import ccall "gtk_print_settings_get_resolution_x" gtk_print_settings_get_resolution_x :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO Int32

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_RESOLUTION_X'.
-- 
-- /Since: 2.16/
printSettingsGetResolutionX ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Int32
    -- ^ __Returns:__ the horizontal resolution in dpi
printSettingsGetResolutionX :: a -> m Int32
printSettingsGetResolutionX settings :: a
settings = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Int32
result <- Ptr PrintSettings -> IO Int32
gtk_print_settings_get_resolution_x Ptr PrintSettings
settings'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetResolutionXMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetResolutionXMethodInfo a signature where
    overloadedMethod = printSettingsGetResolutionX

#endif

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

foreign import ccall "gtk_print_settings_get_resolution_y" gtk_print_settings_get_resolution_y :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO Int32

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_RESOLUTION_Y'.
-- 
-- /Since: 2.16/
printSettingsGetResolutionY ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Int32
    -- ^ __Returns:__ the vertical resolution in dpi
printSettingsGetResolutionY :: a -> m Int32
printSettingsGetResolutionY settings :: a
settings = IO Int32 -> m Int32
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Int32
result <- Ptr PrintSettings -> IO Int32
gtk_print_settings_get_resolution_y Ptr PrintSettings
settings'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Int32 -> IO Int32
forall (m :: * -> *) a. Monad m => a -> m a
return Int32
result

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetResolutionYMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetResolutionYMethodInfo a signature where
    overloadedMethod = printSettingsGetResolutionY

#endif

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

foreign import ccall "gtk_print_settings_get_reverse" gtk_print_settings_get_reverse :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CInt

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_REVERSE'.
-- 
-- /Since: 2.10/
printSettingsGetReverse ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Bool
    -- ^ __Returns:__ whether to reverse the order of the printed pages
printSettingsGetReverse :: a -> m Bool
printSettingsGetReverse settings :: a
settings = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CInt
result <- Ptr PrintSettings -> IO CInt
gtk_print_settings_get_reverse Ptr PrintSettings
settings'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetReverseMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetReverseMethodInfo a signature where
    overloadedMethod = printSettingsGetReverse

#endif

-- method PrintSettings::get_scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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_print_settings_get_scale" gtk_print_settings_get_scale :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CDouble

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_SCALE'.
-- 
-- /Since: 2.10/
printSettingsGetScale ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Double
    -- ^ __Returns:__ the scale in percent
printSettingsGetScale :: a -> m Double
printSettingsGetScale settings :: a
settings = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CDouble
result <- Ptr PrintSettings -> IO CDouble
gtk_print_settings_get_scale Ptr PrintSettings
settings'
    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
settings
    Double -> IO Double
forall (m :: * -> *) a. Monad m => a -> m a
return Double
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetScaleMethodInfo
instance (signature ~ (m Double), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetScaleMethodInfo a signature where
    overloadedMethod = printSettingsGetScale

#endif

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

foreign import ccall "gtk_print_settings_get_use_color" gtk_print_settings_get_use_color :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO CInt

-- | Gets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_USE_COLOR'.
-- 
-- /Since: 2.10/
printSettingsGetUseColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m Bool
    -- ^ __Returns:__ whether to use color
printSettingsGetUseColor :: a -> m Bool
printSettingsGetUseColor settings :: a
settings = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CInt
result <- Ptr PrintSettings -> IO CInt
gtk_print_settings_get_use_color Ptr PrintSettings
settings'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsGetUseColorMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsGetUseColorMethodInfo a signature where
    overloadedMethod = printSettingsGetUseColor

#endif

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

foreign import ccall "gtk_print_settings_has_key" gtk_print_settings_has_key :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    IO CInt

-- | Returns 'P.True', if a value is associated with /@key@/.
-- 
-- /Since: 2.10/
printSettingsHasKey ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> m Bool
    -- ^ __Returns:__ 'P.True', if /@key@/ has a value
printSettingsHasKey :: a -> Text -> m Bool
printSettingsHasKey settings :: a
settings key :: Text
key = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    CInt
result <- Ptr PrintSettings -> CString -> IO CInt
gtk_print_settings_has_key Ptr PrintSettings
settings' CString
key'
    let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsHasKeyMethodInfo
instance (signature ~ (T.Text -> m Bool), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsHasKeyMethodInfo a signature where
    overloadedMethod = printSettingsHasKey

#endif

-- method PrintSettings::load_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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 settings 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_print_settings_load_file" gtk_print_settings_load_file :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- file_name : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Reads the print settings from /@fileName@/. If the file could not be loaded
-- then error is set to either a t'GI.GLib.Enums.FileError' or t'GI.GLib.Enums.KeyFileError'.
-- See 'GI.Gtk.Objects.PrintSettings.printSettingsToFile'.
-- 
-- /Since: 2.14/
printSettingsLoadFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> [Char]
    -- ^ /@fileName@/: the filename to read the settings from
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
printSettingsLoadFile :: a -> [Char] -> m ()
printSettingsLoadFile settings :: a
settings 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    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 PrintSettings -> CString -> Ptr (Ptr GError) -> IO CInt
gtk_print_settings_load_file Ptr PrintSettings
settings' CString
fileName'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
        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 PrintSettingsLoadFileMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsLoadFileMethodInfo a signature where
    overloadedMethod = printSettingsLoadFile

#endif

-- method PrintSettings::load_key_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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 settings 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 to use, or %NULL to use the default\n    \8220Print Settings\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_print_settings_load_key_file" gtk_print_settings_load_key_file :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    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 print settings from the group /@groupName@/ in /@keyFile@/. If the
-- file could not be loaded then error is set to either a t'GI.GLib.Enums.FileError' or
-- t'GI.GLib.Enums.KeyFileError'.
-- 
-- /Since: 2.14/
printSettingsLoadKeyFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> GLib.KeyFile.KeyFile
    -- ^ /@keyFile@/: the t'GI.GLib.Structs.KeyFile.KeyFile' to retrieve the settings from
    -> Maybe (T.Text)
    -- ^ /@groupName@/: the name of the group to use, or 'P.Nothing' to use the default
    --     “Print Settings”
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
printSettingsLoadKeyFile :: a -> KeyFile -> Maybe Text -> m ()
printSettingsLoadKeyFile settings :: a
settings 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    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 PrintSettings
-> Ptr KeyFile -> CString -> Ptr (Ptr GError) -> IO CInt
gtk_print_settings_load_key_file Ptr PrintSettings
settings' Ptr KeyFile
keyFile' CString
maybeGroupName
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
        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 PrintSettingsLoadKeyFileMethodInfo
instance (signature ~ (GLib.KeyFile.KeyFile -> Maybe (T.Text) -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsLoadKeyFileMethodInfo a signature where
    overloadedMethod = printSettingsLoadKeyFile

#endif

-- method PrintSettings::set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a string value, or %NULL"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set" gtk_print_settings_set :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    CString ->                              -- value : TBasicType TUTF8
    IO ()

-- | Associates /@value@/ with /@key@/.
-- 
-- /Since: 2.10/
printSettingsSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> Maybe (T.Text)
    -- ^ /@value@/: a string value, or 'P.Nothing'
    -> m ()
printSettingsSet :: a -> Text -> Maybe Text -> m ()
printSettingsSet settings :: a
settings key :: Text
key value :: Maybe Text
value = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    CString
maybeValue <- case Maybe Text
value of
        Nothing -> CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
forall a. Ptr a
nullPtr
        Just jValue :: Text
jValue -> do
            CString
jValue' <- Text -> IO CString
textToCString Text
jValue
            CString -> IO CString
forall (m :: * -> *) a. Monad m => a -> m a
return CString
jValue'
    Ptr PrintSettings -> CString -> CString -> IO ()
gtk_print_settings_set Ptr PrintSettings
settings' CString
key' CString
maybeValue
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
maybeValue
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetMethodInfo
instance (signature ~ (T.Text -> Maybe (T.Text) -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetMethodInfo a signature where
    overloadedMethod = printSettingsSet

#endif

-- method PrintSettings::set_bool
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a boolean" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_bool" gtk_print_settings_set_bool :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    CInt ->                                 -- value : TBasicType TBoolean
    IO ()

-- | Sets /@key@/ to a boolean value.
-- 
-- /Since: 2.10/
printSettingsSetBool ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> Bool
    -- ^ /@value@/: a boolean
    -> m ()
printSettingsSetBool :: a -> Text -> Bool -> m ()
printSettingsSetBool settings :: a
settings key :: Text
key value :: Bool
value = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    let value' :: CInt
value' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
value
    Ptr PrintSettings -> CString -> CInt -> IO ()
gtk_print_settings_set_bool Ptr PrintSettings
settings' CString
key' CInt
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetBoolMethodInfo
instance (signature ~ (T.Text -> Bool -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetBoolMethodInfo a signature where
    overloadedMethod = printSettingsSetBool

#endif

-- method PrintSettings::set_collate
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "collate"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to collate the output"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_collate" gtk_print_settings_set_collate :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CInt ->                                 -- collate : TBasicType TBoolean
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_COLLATE'.
-- 
-- /Since: 2.10/
printSettingsSetCollate ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Bool
    -- ^ /@collate@/: whether to collate the output
    -> m ()
printSettingsSetCollate :: a -> Bool -> m ()
printSettingsSetCollate settings :: a
settings collate :: Bool
collate = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let collate' :: CInt
collate' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
collate
    Ptr PrintSettings -> CInt -> IO ()
gtk_print_settings_set_collate Ptr PrintSettings
settings' CInt
collate'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetCollateMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetCollateMethodInfo a signature where
    overloadedMethod = printSettingsSetCollate

#endif

-- method PrintSettings::set_default_source
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "default_source"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the default source" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_default_source" gtk_print_settings_set_default_source :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- default_source : TBasicType TUTF8
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_DEFAULT_SOURCE'.
-- 
-- /Since: 2.10/
printSettingsSetDefaultSource ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@defaultSource@/: the default source
    -> m ()
printSettingsSetDefaultSource :: a -> Text -> m ()
printSettingsSetDefaultSource settings :: a
settings defaultSource :: Text
defaultSource = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
defaultSource' <- Text -> IO CString
textToCString Text
defaultSource
    Ptr PrintSettings -> CString -> IO ()
gtk_print_settings_set_default_source Ptr PrintSettings
settings' CString
defaultSource'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
defaultSource'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetDefaultSourceMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetDefaultSourceMethodInfo a signature where
    overloadedMethod = printSettingsSetDefaultSource

#endif

-- method PrintSettings::set_dither
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "dither"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the dithering that is used"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_dither" gtk_print_settings_set_dither :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- dither : TBasicType TUTF8
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_DITHER'.
-- 
-- /Since: 2.10/
printSettingsSetDither ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@dither@/: the dithering that is used
    -> m ()
printSettingsSetDither :: a -> Text -> m ()
printSettingsSetDither settings :: a
settings dither :: Text
dither = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
dither' <- Text -> IO CString
textToCString Text
dither
    Ptr PrintSettings -> CString -> IO ()
gtk_print_settings_set_dither Ptr PrintSettings
settings' CString
dither'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
dither'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetDitherMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetDitherMethodInfo a signature where
    overloadedMethod = printSettingsSetDither

#endif

-- method PrintSettings::set_double
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a double 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_print_settings_set_double" gtk_print_settings_set_double :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    CDouble ->                              -- value : TBasicType TDouble
    IO ()

-- | Sets /@key@/ to a double value.
-- 
-- /Since: 2.10/
printSettingsSetDouble ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> Double
    -- ^ /@value@/: a double value
    -> m ()
printSettingsSetDouble :: a -> Text -> Double -> m ()
printSettingsSetDouble settings :: a
settings key :: Text
key value :: Double
value = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    let value' :: CDouble
value' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
value
    Ptr PrintSettings -> CString -> CDouble -> IO ()
gtk_print_settings_set_double Ptr PrintSettings
settings' CString
key' CDouble
value'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetDoubleMethodInfo
instance (signature ~ (T.Text -> Double -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetDoubleMethodInfo a signature where
    overloadedMethod = printSettingsSetDouble

#endif

-- method PrintSettings::set_duplex
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "duplex"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintDuplex" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintDuplex 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_print_settings_set_duplex" gtk_print_settings_set_duplex :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CUInt ->                                -- duplex : TInterface (Name {namespace = "Gtk", name = "PrintDuplex"})
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_DUPLEX'.
-- 
-- /Since: 2.10/
printSettingsSetDuplex ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.Enums.PrintDuplex
    -- ^ /@duplex@/: a t'GI.Gtk.Enums.PrintDuplex' value
    -> m ()
printSettingsSetDuplex :: a -> PrintDuplex -> m ()
printSettingsSetDuplex settings :: a
settings duplex :: PrintDuplex
duplex = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let duplex' :: CUInt
duplex' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PrintDuplex -> Int) -> PrintDuplex -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PrintDuplex -> Int
forall a. Enum a => a -> Int
fromEnum) PrintDuplex
duplex
    Ptr PrintSettings -> CUInt -> IO ()
gtk_print_settings_set_duplex Ptr PrintSettings
settings' CUInt
duplex'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetDuplexMethodInfo
instance (signature ~ (Gtk.Enums.PrintDuplex -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetDuplexMethodInfo a signature where
    overloadedMethod = printSettingsSetDuplex

#endif

-- method PrintSettings::set_finishings
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "finishings"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the finishings" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_finishings" gtk_print_settings_set_finishings :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- finishings : TBasicType TUTF8
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_FINISHINGS'.
-- 
-- /Since: 2.10/
printSettingsSetFinishings ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@finishings@/: the finishings
    -> m ()
printSettingsSetFinishings :: a -> Text -> m ()
printSettingsSetFinishings settings :: a
settings finishings :: Text
finishings = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
finishings' <- Text -> IO CString
textToCString Text
finishings
    Ptr PrintSettings -> CString -> IO ()
gtk_print_settings_set_finishings Ptr PrintSettings
settings' CString
finishings'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
finishings'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetFinishingsMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetFinishingsMethodInfo a signature where
    overloadedMethod = printSettingsSetFinishings

#endif

-- method PrintSettings::set_int
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an integer" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_int" gtk_print_settings_set_int :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    Int32 ->                                -- value : TBasicType TInt
    IO ()

-- | Sets /@key@/ to an integer value.
-- 
-- /Since: 2.10/
printSettingsSetInt ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> Int32
    -- ^ /@value@/: an integer
    -> m ()
printSettingsSetInt :: a -> Text -> Int32 -> m ()
printSettingsSetInt settings :: a
settings key :: Text
key value :: Int32
value = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr PrintSettings -> CString -> Int32 -> IO ()
gtk_print_settings_set_int Ptr PrintSettings
settings' CString
key' Int32
value
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetIntMethodInfo
instance (signature ~ (T.Text -> Int32 -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetIntMethodInfo a signature where
    overloadedMethod = printSettingsSetInt

#endif

-- method PrintSettings::set_length
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "value"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a length" , 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 of @length"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_length" gtk_print_settings_set_length :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    CDouble ->                              -- value : TBasicType TDouble
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO ()

-- | Associates a length in units of /@unit@/ with /@key@/.
-- 
-- /Since: 2.10/
printSettingsSetLength ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> Double
    -- ^ /@value@/: a length
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the unit of /@length@/
    -> m ()
printSettingsSetLength :: a -> Text -> Double -> Unit -> m ()
printSettingsSetLength settings :: a
settings key :: Text
key value :: Double
value 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    let value' :: CDouble
value' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
value
    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 PrintSettings -> CString -> CDouble -> CUInt -> IO ()
gtk_print_settings_set_length Ptr PrintSettings
settings' CString
key' CDouble
value' CUInt
unit'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetLengthMethodInfo
instance (signature ~ (T.Text -> Double -> Gtk.Enums.Unit -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetLengthMethodInfo a signature where
    overloadedMethod = printSettingsSetLength

#endif

-- method PrintSettings::set_media_type
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "media_type"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the media type" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_media_type" gtk_print_settings_set_media_type :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- media_type : TBasicType TUTF8
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_MEDIA_TYPE'.
-- 
-- The set of media types is defined in PWG 5101.1-2002 PWG.
-- 
-- /Since: 2.10/
printSettingsSetMediaType ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@mediaType@/: the media type
    -> m ()
printSettingsSetMediaType :: a -> Text -> m ()
printSettingsSetMediaType settings :: a
settings mediaType :: Text
mediaType = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
mediaType' <- Text -> IO CString
textToCString Text
mediaType
    Ptr PrintSettings -> CString -> IO ()
gtk_print_settings_set_media_type Ptr PrintSettings
settings' CString
mediaType'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
mediaType'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetMediaTypeMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetMediaTypeMethodInfo a signature where
    overloadedMethod = printSettingsSetMediaType

#endif

-- method PrintSettings::set_n_copies
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_copies"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of copies"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_n_copies" gtk_print_settings_set_n_copies :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    Int32 ->                                -- num_copies : TBasicType TInt
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_N_COPIES'.
-- 
-- /Since: 2.10/
printSettingsSetNCopies ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Int32
    -- ^ /@numCopies@/: the number of copies
    -> m ()
printSettingsSetNCopies :: a -> Int32 -> m ()
printSettingsSetNCopies settings :: a
settings numCopies :: Int32
numCopies = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Ptr PrintSettings -> Int32 -> IO ()
gtk_print_settings_set_n_copies Ptr PrintSettings
settings' Int32
numCopies
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetNCopiesMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetNCopiesMethodInfo a signature where
    overloadedMethod = printSettingsSetNCopies

#endif

-- method PrintSettings::set_number_up
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "number_up"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the number of pages per sheet"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_number_up" gtk_print_settings_set_number_up :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    Int32 ->                                -- number_up : TBasicType TInt
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_NUMBER_UP'.
-- 
-- /Since: 2.10/
printSettingsSetNumberUp ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Int32
    -- ^ /@numberUp@/: the number of pages per sheet
    -> m ()
printSettingsSetNumberUp :: a -> Int32 -> m ()
printSettingsSetNumberUp settings :: a
settings numberUp :: Int32
numberUp = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Ptr PrintSettings -> Int32 -> IO ()
gtk_print_settings_set_number_up Ptr PrintSettings
settings' Int32
numberUp
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetNumberUpMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetNumberUpMethodInfo a signature where
    overloadedMethod = printSettingsSetNumberUp

#endif

-- method PrintSettings::set_number_up_layout
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "number_up_layout"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "NumberUpLayout" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkNumberUpLayout 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_print_settings_set_number_up_layout" gtk_print_settings_set_number_up_layout :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CUInt ->                                -- number_up_layout : TInterface (Name {namespace = "Gtk", name = "NumberUpLayout"})
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_NUMBER_UP_LAYOUT'.
-- 
-- /Since: 2.14/
printSettingsSetNumberUpLayout ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.Enums.NumberUpLayout
    -- ^ /@numberUpLayout@/: a t'GI.Gtk.Enums.NumberUpLayout' value
    -> m ()
printSettingsSetNumberUpLayout :: a -> NumberUpLayout -> m ()
printSettingsSetNumberUpLayout settings :: a
settings numberUpLayout :: NumberUpLayout
numberUpLayout = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let numberUpLayout' :: CUInt
numberUpLayout' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt)
-> (NumberUpLayout -> Int) -> NumberUpLayout -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NumberUpLayout -> Int
forall a. Enum a => a -> Int
fromEnum) NumberUpLayout
numberUpLayout
    Ptr PrintSettings -> CUInt -> IO ()
gtk_print_settings_set_number_up_layout Ptr PrintSettings
settings' CUInt
numberUpLayout'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetNumberUpLayoutMethodInfo
instance (signature ~ (Gtk.Enums.NumberUpLayout -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetNumberUpLayoutMethodInfo a signature where
    overloadedMethod = printSettingsSetNumberUpLayout

#endif

-- method PrintSettings::set_orientation
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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 page orientation" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_orientation" gtk_print_settings_set_orientation :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CUInt ->                                -- orientation : TInterface (Name {namespace = "Gtk", name = "PageOrientation"})
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_ORIENTATION'.
-- 
-- /Since: 2.10/
printSettingsSetOrientation ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.Enums.PageOrientation
    -- ^ /@orientation@/: a page orientation
    -> m ()
printSettingsSetOrientation :: a -> PageOrientation -> m ()
printSettingsSetOrientation settings :: a
settings 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    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 PrintSettings -> CUInt -> IO ()
gtk_print_settings_set_orientation Ptr PrintSettings
settings' CUInt
orientation'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

-- method PrintSettings::set_output_bin
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "output_bin"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the output bin" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_output_bin" gtk_print_settings_set_output_bin :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- output_bin : TBasicType TUTF8
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_OUTPUT_BIN'.
-- 
-- /Since: 2.10/
printSettingsSetOutputBin ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@outputBin@/: the output bin
    -> m ()
printSettingsSetOutputBin :: a -> Text -> m ()
printSettingsSetOutputBin settings :: a
settings outputBin :: Text
outputBin = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
outputBin' <- Text -> IO CString
textToCString Text
outputBin
    Ptr PrintSettings -> CString -> IO ()
gtk_print_settings_set_output_bin Ptr PrintSettings
settings' CString
outputBin'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
outputBin'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetOutputBinMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetOutputBinMethodInfo a signature where
    overloadedMethod = printSettingsSetOutputBin

#endif

-- method PrintSettings::set_page_ranges
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "page_ranges"
--           , argType =
--               TCArray
--                 False
--                 (-1)
--                 2
--                 (TInterface Name { namespace = "Gtk" , name = "PageRange" })
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "an array of #GtkPageRanges"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "num_ranges"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the length of @page_ranges"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: [ Arg
--              { argCName = "num_ranges"
--              , argType = TBasicType TInt
--              , direction = DirectionIn
--              , mayBeNull = False
--              , argDoc =
--                  Documentation
--                    { rawDocText = Just "the length of @page_ranges"
--                    , sinceVersion = Nothing
--                    }
--              , argScope = ScopeTypeInvalid
--              , argClosure = -1
--              , argDestroy = -1
--              , argCallerAllocates = False
--              , transfer = TransferNothing
--              }
--          ]
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_page_ranges" gtk_print_settings_set_page_ranges :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    Ptr Gtk.PageRange.PageRange ->          -- page_ranges : TCArray False (-1) 2 (TInterface (Name {namespace = "Gtk", name = "PageRange"}))
    Int32 ->                                -- num_ranges : TBasicType TInt
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAGE_RANGES'.
-- 
-- /Since: 2.10/
printSettingsSetPageRanges ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> [Gtk.PageRange.PageRange]
    -- ^ /@pageRanges@/: an array of @/GtkPageRanges/@
    -> m ()
printSettingsSetPageRanges :: a -> [PageRange] -> m ()
printSettingsSetPageRanges settings :: a
settings pageRanges :: [PageRange]
pageRanges = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    let numRanges :: Int32
numRanges = Int -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Int32) -> Int -> Int32
forall a b. (a -> b) -> a -> b
$ [PageRange] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [PageRange]
pageRanges
    Ptr PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    [Ptr PageRange]
pageRanges' <- (PageRange -> IO (Ptr PageRange))
-> [PageRange] -> IO [Ptr PageRange]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM PageRange -> IO (Ptr PageRange)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr [PageRange]
pageRanges
    Ptr PageRange
pageRanges'' <- Int -> [Ptr PageRange] -> IO (Ptr PageRange)
forall a. Int -> [Ptr a] -> IO (Ptr a)
packBlockArray 8 [Ptr PageRange]
pageRanges'
    Ptr PrintSettings -> Ptr PageRange -> Int32 -> IO ()
gtk_print_settings_set_page_ranges Ptr PrintSettings
settings' Ptr PageRange
pageRanges'' Int32
numRanges
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    (PageRange -> IO ()) -> [PageRange] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ PageRange -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr [PageRange]
pageRanges
    Ptr PageRange -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr PageRange
pageRanges''
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetPageRangesMethodInfo
instance (signature ~ ([Gtk.PageRange.PageRange] -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetPageRangesMethodInfo a signature where
    overloadedMethod = printSettingsSetPageRanges

#endif

-- method PrintSettings::set_page_set
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "page_set"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PageSet" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPageSet 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_print_settings_set_page_set" gtk_print_settings_set_page_set :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CUInt ->                                -- page_set : TInterface (Name {namespace = "Gtk", name = "PageSet"})
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAGE_SET'.
-- 
-- /Since: 2.10/
printSettingsSetPageSet ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.Enums.PageSet
    -- ^ /@pageSet@/: a t'GI.Gtk.Enums.PageSet' value
    -> m ()
printSettingsSetPageSet :: a -> PageSet -> m ()
printSettingsSetPageSet settings :: a
settings pageSet :: PageSet
pageSet = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let pageSet' :: CUInt
pageSet' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PageSet -> Int) -> PageSet -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PageSet -> Int
forall a. Enum a => a -> Int
fromEnum) PageSet
pageSet
    Ptr PrintSettings -> CUInt -> IO ()
gtk_print_settings_set_page_set Ptr PrintSettings
settings' CUInt
pageSet'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetPageSetMethodInfo
instance (signature ~ (Gtk.Enums.PageSet -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetPageSetMethodInfo a signature where
    overloadedMethod = printSettingsSetPageSet

#endif

-- method PrintSettings::set_paper_height
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "height"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the paper height" , 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 of @height"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_paper_height" gtk_print_settings_set_paper_height :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CDouble ->                              -- height : TBasicType TDouble
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAPER_HEIGHT'.
-- 
-- /Since: 2.10/
printSettingsSetPaperHeight ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Double
    -- ^ /@height@/: the paper height
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the units of /@height@/
    -> m ()
printSettingsSetPaperHeight :: a -> Double -> Unit -> m ()
printSettingsSetPaperHeight settings :: a
settings height :: Double
height 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let height' :: CDouble
height' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
height
    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 PrintSettings -> CDouble -> CUInt -> IO ()
gtk_print_settings_set_paper_height Ptr PrintSettings
settings' CDouble
height' CUInt
unit'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

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

foreign import ccall "gtk_print_settings_set_paper_size" gtk_print_settings_set_paper_size :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    Ptr Gtk.PaperSize.PaperSize ->          -- paper_size : TInterface (Name {namespace = "Gtk", name = "PaperSize"})
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAPER_FORMAT',
-- 'GI.Gtk.Constants.PRINT_SETTINGS_PAPER_WIDTH' and
-- 'GI.Gtk.Constants.PRINT_SETTINGS_PAPER_HEIGHT'.
-- 
-- /Since: 2.10/
printSettingsSetPaperSize ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.PaperSize.PaperSize
    -- ^ /@paperSize@/: a paper size
    -> m ()
printSettingsSetPaperSize :: a -> PaperSize -> m ()
printSettingsSetPaperSize settings :: a
settings paperSize :: PaperSize
paperSize = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Ptr PaperSize
paperSize' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
paperSize
    Ptr PrintSettings -> Ptr PaperSize -> IO ()
gtk_print_settings_set_paper_size Ptr PrintSettings
settings' Ptr PaperSize
paperSize'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    PaperSize -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr PaperSize
paperSize
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

-- method PrintSettings::set_paper_width
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "width"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the paper width" , 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 of @width"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_paper_width" gtk_print_settings_set_paper_width :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CDouble ->                              -- width : TBasicType TDouble
    CUInt ->                                -- unit : TInterface (Name {namespace = "Gtk", name = "Unit"})
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PAPER_WIDTH'.
-- 
-- /Since: 2.10/
printSettingsSetPaperWidth ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Double
    -- ^ /@width@/: the paper width
    -> Gtk.Enums.Unit
    -- ^ /@unit@/: the units of /@width@/
    -> m ()
printSettingsSetPaperWidth :: a -> Double -> Unit -> m ()
printSettingsSetPaperWidth settings :: a
settings width :: Double
width 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let width' :: CDouble
width' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
width
    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 PrintSettings -> CDouble -> CUInt -> IO ()
gtk_print_settings_set_paper_width Ptr PrintSettings
settings' CDouble
width' CUInt
unit'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

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

#endif

-- method PrintSettings::set_print_pages
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "pages"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintPages" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintPages 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_print_settings_set_print_pages" gtk_print_settings_set_print_pages :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CUInt ->                                -- pages : TInterface (Name {namespace = "Gtk", name = "PrintPages"})
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PRINT_PAGES'.
-- 
-- /Since: 2.10/
printSettingsSetPrintPages ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.Enums.PrintPages
    -- ^ /@pages@/: a t'GI.Gtk.Enums.PrintPages' value
    -> m ()
printSettingsSetPrintPages :: a -> PrintPages -> m ()
printSettingsSetPrintPages settings :: a
settings pages :: PrintPages
pages = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let pages' :: CUInt
pages' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PrintPages -> Int) -> PrintPages -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PrintPages -> Int
forall a. Enum a => a -> Int
fromEnum) PrintPages
pages
    Ptr PrintSettings -> CUInt -> IO ()
gtk_print_settings_set_print_pages Ptr PrintSettings
settings' CUInt
pages'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetPrintPagesMethodInfo
instance (signature ~ (Gtk.Enums.PrintPages -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetPrintPagesMethodInfo a signature where
    overloadedMethod = printSettingsSetPrintPages

#endif

-- method PrintSettings::set_printer
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "printer"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the printer name" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_printer" gtk_print_settings_set_printer :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- printer : TBasicType TUTF8
    IO ()

-- | Convenience function to set 'GI.Gtk.Constants.PRINT_SETTINGS_PRINTER'
-- to /@printer@/.
-- 
-- /Since: 2.10/
printSettingsSetPrinter ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@printer@/: the printer name
    -> m ()
printSettingsSetPrinter :: a -> Text -> m ()
printSettingsSetPrinter settings :: a
settings printer :: Text
printer = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
printer' <- Text -> IO CString
textToCString Text
printer
    Ptr PrintSettings -> CString -> IO ()
gtk_print_settings_set_printer Ptr PrintSettings
settings' CString
printer'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
printer'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetPrinterMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetPrinterMethodInfo a signature where
    overloadedMethod = printSettingsSetPrinter

#endif

-- method PrintSettings::set_printer_lpi
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "lpi"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the resolution in lpi (lines per inch)"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_printer_lpi" gtk_print_settings_set_printer_lpi :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CDouble ->                              -- lpi : TBasicType TDouble
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_PRINTER_LPI'.
-- 
-- /Since: 2.16/
printSettingsSetPrinterLpi ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Double
    -- ^ /@lpi@/: the resolution in lpi (lines per inch)
    -> m ()
printSettingsSetPrinterLpi :: a -> Double -> m ()
printSettingsSetPrinterLpi settings :: a
settings lpi :: Double
lpi = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let lpi' :: CDouble
lpi' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
lpi
    Ptr PrintSettings -> CDouble -> IO ()
gtk_print_settings_set_printer_lpi Ptr PrintSettings
settings' CDouble
lpi'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetPrinterLpiMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetPrinterLpiMethodInfo a signature where
    overloadedMethod = printSettingsSetPrinterLpi

#endif

-- method PrintSettings::set_quality
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "quality"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintQuality" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintQuality 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_print_settings_set_quality" gtk_print_settings_set_quality :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CUInt ->                                -- quality : TInterface (Name {namespace = "Gtk", name = "PrintQuality"})
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_QUALITY'.
-- 
-- /Since: 2.10/
printSettingsSetQuality ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Gtk.Enums.PrintQuality
    -- ^ /@quality@/: a t'GI.Gtk.Enums.PrintQuality' value
    -> m ()
printSettingsSetQuality :: a -> PrintQuality -> m ()
printSettingsSetQuality settings :: a
settings quality :: PrintQuality
quality = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let quality' :: CUInt
quality' = (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CUInt) -> (PrintQuality -> Int) -> PrintQuality -> CUInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PrintQuality -> Int
forall a. Enum a => a -> Int
fromEnum) PrintQuality
quality
    Ptr PrintSettings -> CUInt -> IO ()
gtk_print_settings_set_quality Ptr PrintSettings
settings' CUInt
quality'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetQualityMethodInfo
instance (signature ~ (Gtk.Enums.PrintQuality -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetQualityMethodInfo a signature where
    overloadedMethod = printSettingsSetQuality

#endif

-- method PrintSettings::set_resolution
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "resolution"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the resolution in dpi"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_resolution" gtk_print_settings_set_resolution :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    Int32 ->                                -- resolution : TBasicType TInt
    IO ()

-- | Sets the values of 'GI.Gtk.Constants.PRINT_SETTINGS_RESOLUTION',
-- 'GI.Gtk.Constants.PRINT_SETTINGS_RESOLUTION_X' and
-- 'GI.Gtk.Constants.PRINT_SETTINGS_RESOLUTION_Y'.
-- 
-- /Since: 2.10/
printSettingsSetResolution ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Int32
    -- ^ /@resolution@/: the resolution in dpi
    -> m ()
printSettingsSetResolution :: a -> Int32 -> m ()
printSettingsSetResolution settings :: a
settings resolution :: Int32
resolution = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Ptr PrintSettings -> Int32 -> IO ()
gtk_print_settings_set_resolution Ptr PrintSettings
settings' Int32
resolution
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetResolutionMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetResolutionMethodInfo a signature where
    overloadedMethod = printSettingsSetResolution

#endif

-- method PrintSettings::set_resolution_xy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "resolution_x"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the horizontal resolution in dpi"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "resolution_y"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the vertical resolution in dpi"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_resolution_xy" gtk_print_settings_set_resolution_xy :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    Int32 ->                                -- resolution_x : TBasicType TInt
    Int32 ->                                -- resolution_y : TBasicType TInt
    IO ()

-- | Sets the values of 'GI.Gtk.Constants.PRINT_SETTINGS_RESOLUTION',
-- 'GI.Gtk.Constants.PRINT_SETTINGS_RESOLUTION_X' and
-- 'GI.Gtk.Constants.PRINT_SETTINGS_RESOLUTION_Y'.
-- 
-- /Since: 2.16/
printSettingsSetResolutionXy ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Int32
    -- ^ /@resolutionX@/: the horizontal resolution in dpi
    -> Int32
    -- ^ /@resolutionY@/: the vertical resolution in dpi
    -> m ()
printSettingsSetResolutionXy :: a -> Int32 -> Int32 -> m ()
printSettingsSetResolutionXy settings :: a
settings resolutionX :: Int32
resolutionX resolutionY :: Int32
resolutionY = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Ptr PrintSettings -> Int32 -> Int32 -> IO ()
gtk_print_settings_set_resolution_xy Ptr PrintSettings
settings' Int32
resolutionX Int32
resolutionY
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetResolutionXyMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetResolutionXyMethodInfo a signature where
    overloadedMethod = printSettingsSetResolutionXy

#endif

-- method PrintSettings::set_reverse
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "reverse"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to reverse the output"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_reverse" gtk_print_settings_set_reverse :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CInt ->                                 -- reverse : TBasicType TBoolean
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_REVERSE'.
-- 
-- /Since: 2.10/
printSettingsSetReverse ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Bool
    -- ^ /@reverse@/: whether to reverse the output
    -> m ()
printSettingsSetReverse :: a -> Bool -> m ()
printSettingsSetReverse settings :: a
settings reverse :: Bool
reverse = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let reverse' :: CInt
reverse' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
reverse
    Ptr PrintSettings -> CInt -> IO ()
gtk_print_settings_set_reverse Ptr PrintSettings
settings' CInt
reverse'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetReverseMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetReverseMethodInfo a signature where
    overloadedMethod = printSettingsSetReverse

#endif

-- method PrintSettings::set_scale
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "scale"
--           , argType = TBasicType TDouble
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the scale in percent"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_scale" gtk_print_settings_set_scale :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CDouble ->                              -- scale : TBasicType TDouble
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_SCALE'.
-- 
-- /Since: 2.10/
printSettingsSetScale ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Double
    -- ^ /@scale@/: the scale in percent
    -> m ()
printSettingsSetScale :: a -> Double -> m ()
printSettingsSetScale settings :: a
settings scale :: Double
scale = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let scale' :: CDouble
scale' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
scale
    Ptr PrintSettings -> CDouble -> IO ()
gtk_print_settings_set_scale Ptr PrintSettings
settings' CDouble
scale'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetScaleMethodInfo
instance (signature ~ (Double -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetScaleMethodInfo a signature where
    overloadedMethod = printSettingsSetScale

#endif

-- method PrintSettings::set_use_color
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use_color"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to use color"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_set_use_color" gtk_print_settings_set_use_color :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CInt ->                                 -- use_color : TBasicType TBoolean
    IO ()

-- | Sets the value of 'GI.Gtk.Constants.PRINT_SETTINGS_USE_COLOR'.
-- 
-- /Since: 2.10/
printSettingsSetUseColor ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> Bool
    -- ^ /@useColor@/: whether to use color
    -> m ()
printSettingsSetUseColor :: a -> Bool -> m ()
printSettingsSetUseColor settings :: a
settings useColor :: Bool
useColor = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    let useColor' :: CInt
useColor' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum) Bool
useColor
    Ptr PrintSettings -> CInt -> IO ()
gtk_print_settings_set_use_color Ptr PrintSettings
settings' CInt
useColor'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsSetUseColorMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsSetUseColorMethodInfo a signature where
    overloadedMethod = printSettingsSetUseColor

#endif

-- method PrintSettings::to_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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_print_settings_to_file" gtk_print_settings_to_file :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- file_name : TBasicType TFileName
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | This function saves the print settings from /@settings@/ to /@fileName@/. If the
-- file could not be loaded then error is set to either a t'GI.GLib.Enums.FileError' or
-- t'GI.GLib.Enums.KeyFileError'.
-- 
-- /Since: 2.12/
printSettingsToFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> [Char]
    -- ^ /@fileName@/: the file to save to
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
printSettingsToFile :: a -> [Char] -> m ()
printSettingsToFile settings :: a
settings 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    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 PrintSettings -> CString -> Ptr (Ptr GError) -> IO CInt
gtk_print_settings_to_file Ptr PrintSettings
settings' CString
fileName'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
        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 PrintSettingsToFileMethodInfo
instance (signature ~ ([Char] -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsToFileMethodInfo a signature where
    overloadedMethod = printSettingsToFile

#endif

-- method PrintSettings::to_gvariant
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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_print_settings_to_gvariant" gtk_print_settings_to_gvariant :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    IO (Ptr GVariant)

-- | Serialize print settings to an a{sv} variant.
-- 
-- /Since: 3.22/
printSettingsToGvariant ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> m GVariant
    -- ^ __Returns:__ a new, floating, t'GVariant'
printSettingsToGvariant :: a -> m GVariant
printSettingsToGvariant settings :: a
settings = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    Ptr GVariant
result <- Ptr PrintSettings -> IO (Ptr GVariant)
gtk_print_settings_to_gvariant Ptr PrintSettings
settings'
    Text -> Ptr GVariant -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL "printSettingsToGvariant" 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
settings
    GVariant -> IO GVariant
forall (m :: * -> *) a. Monad m => a -> m a
return GVariant
result'

#if defined(ENABLE_OVERLOADING)
data PrintSettingsToGvariantMethodInfo
instance (signature ~ (m GVariant), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsToGvariantMethodInfo a signature where
    overloadedMethod = printSettingsToGvariant

#endif

-- method PrintSettings::to_key_file
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , 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 print settings 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, or\n    %NULL to use the default \8220Print Settings\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_print_settings_to_key_file" gtk_print_settings_to_key_file :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    Ptr GLib.KeyFile.KeyFile ->             -- key_file : TInterface (Name {namespace = "GLib", name = "KeyFile"})
    CString ->                              -- group_name : TBasicType TUTF8
    IO ()

-- | This function adds the print settings from /@settings@/ to /@keyFile@/.
-- 
-- /Since: 2.12/
printSettingsToKeyFile ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> GLib.KeyFile.KeyFile
    -- ^ /@keyFile@/: the t'GI.GLib.Structs.KeyFile.KeyFile' to save the print settings to
    -> Maybe (T.Text)
    -- ^ /@groupName@/: the group to add the settings to in /@keyFile@/, or
    --     'P.Nothing' to use the default “Print Settings”
    -> m ()
printSettingsToKeyFile :: a -> KeyFile -> Maybe Text -> m ()
printSettingsToKeyFile settings :: a
settings 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    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 PrintSettings -> Ptr KeyFile -> CString -> IO ()
gtk_print_settings_to_key_file Ptr PrintSettings
settings' Ptr KeyFile
keyFile' CString
maybeGroupName
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    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 PrintSettingsToKeyFileMethodInfo
instance (signature ~ (GLib.KeyFile.KeyFile -> Maybe (T.Text) -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsToKeyFileMethodInfo a signature where
    overloadedMethod = printSettingsToKeyFile

#endif

-- method PrintSettings::unset
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "settings"
--           , argType =
--               TInterface Name { namespace = "Gtk" , name = "PrintSettings" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a #GtkPrintSettings"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "key"
--           , argType = TBasicType TUTF8
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a key" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gtk_print_settings_unset" gtk_print_settings_unset :: 
    Ptr PrintSettings ->                    -- settings : TInterface (Name {namespace = "Gtk", name = "PrintSettings"})
    CString ->                              -- key : TBasicType TUTF8
    IO ()

-- | Removes any value associated with /@key@/.
-- This has the same effect as setting the value to 'P.Nothing'.
-- 
-- /Since: 2.10/
printSettingsUnset ::
    (B.CallStack.HasCallStack, MonadIO m, IsPrintSettings a) =>
    a
    -- ^ /@settings@/: a t'GI.Gtk.Objects.PrintSettings.PrintSettings'
    -> T.Text
    -- ^ /@key@/: a key
    -> m ()
printSettingsUnset :: a -> Text -> m ()
printSettingsUnset settings :: a
settings key :: Text
key = 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 PrintSettings
settings' <- a -> IO (Ptr PrintSettings)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
settings
    CString
key' <- Text -> IO CString
textToCString Text
key
    Ptr PrintSettings -> CString -> IO ()
gtk_print_settings_unset Ptr PrintSettings
settings' CString
key'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
settings
    CString -> IO ()
forall a. Ptr a -> IO ()
freeMem CString
key'
    () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data PrintSettingsUnsetMethodInfo
instance (signature ~ (T.Text -> m ()), MonadIO m, IsPrintSettings a) => O.MethodInfo PrintSettingsUnsetMethodInfo a signature where
    overloadedMethod = printSettingsUnset

#endif