{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.PrintSetup
(
PrintSetup(..) ,
#if defined(ENABLE_OVERLOADING)
ResolvePrintSetupMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PrintSetupGetPageSetupMethodInfo ,
#endif
printSetupGetPageSetup ,
#if defined(ENABLE_OVERLOADING)
PrintSetupGetPrintSettingsMethodInfo ,
#endif
printSetupGetPrintSettings ,
#if defined(ENABLE_OVERLOADING)
PrintSetupRefMethodInfo ,
#endif
printSetupRef ,
#if defined(ENABLE_OVERLOADING)
PrintSetupUnrefMethodInfo ,
#endif
printSetupUnref ,
) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GHashTable as B.GHT
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.Kind as DK
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified Data.Word as DW
import qualified Data.Int as DI
import qualified System.Posix.Types as SPT
import qualified Foreign.C.Types as FCT
#if MIN_VERSION_base(4,18,0)
import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gtk.Callbacks as Gtk.Callbacks
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings
import {-# SOURCE #-} qualified GI.Gtk.Structs.PageRange as Gtk.PageRange
import {-# SOURCE #-} qualified GI.Gtk.Structs.PaperSize as Gtk.PaperSize
#else
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Objects.PrintSettings as Gtk.PrintSettings
#endif
newtype PrintSetup = PrintSetup (SP.ManagedPtr PrintSetup)
deriving (PrintSetup -> PrintSetup -> Bool
(PrintSetup -> PrintSetup -> Bool)
-> (PrintSetup -> PrintSetup -> Bool) -> Eq PrintSetup
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PrintSetup -> PrintSetup -> Bool
== :: PrintSetup -> PrintSetup -> Bool
$c/= :: PrintSetup -> PrintSetup -> Bool
/= :: PrintSetup -> PrintSetup -> Bool
Eq)
instance SP.ManagedPtrNewtype PrintSetup where
toManagedPtr :: PrintSetup -> ManagedPtr PrintSetup
toManagedPtr (PrintSetup ManagedPtr PrintSetup
p) = ManagedPtr PrintSetup
p
foreign import ccall "gtk_print_setup_get_type" c_gtk_print_setup_get_type ::
IO GType
type instance O.ParentTypes PrintSetup = '[]
instance O.HasParentTypes PrintSetup
instance B.Types.TypedObject PrintSetup where
glibType :: IO GType
glibType = IO GType
c_gtk_print_setup_get_type
instance B.Types.GBoxed PrintSetup
instance B.GValue.IsGValue (Maybe PrintSetup) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_print_setup_get_type
gvalueSet_ :: Ptr GValue -> Maybe PrintSetup -> IO ()
gvalueSet_ Ptr GValue
gv Maybe PrintSetup
P.Nothing = Ptr GValue -> Ptr PrintSetup -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr PrintSetup
forall a. Ptr a
FP.nullPtr :: FP.Ptr PrintSetup)
gvalueSet_ Ptr GValue
gv (P.Just PrintSetup
obj) = PrintSetup -> (Ptr PrintSetup -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PrintSetup
obj (Ptr GValue -> Ptr PrintSetup -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe PrintSetup)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr PrintSetup)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr PrintSetup)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newBoxed PrintSetup ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PrintSetup
type instance O.AttributeList PrintSetup = PrintSetupAttributeList
type PrintSetupAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_print_setup_get_page_setup" gtk_print_setup_get_page_setup ::
Ptr PrintSetup ->
IO (Ptr Gtk.PageSetup.PageSetup)
printSetupGetPageSetup ::
(B.CallStack.HasCallStack, MonadIO m) =>
PrintSetup
-> m Gtk.PageSetup.PageSetup
printSetupGetPageSetup :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PrintSetup -> m PageSetup
printSetupGetPageSetup PrintSetup
setup = IO PageSetup -> m PageSetup
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PageSetup -> m PageSetup) -> IO PageSetup -> m PageSetup
forall a b. (a -> b) -> a -> b
$ do
setup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
setup
result <- gtk_print_setup_get_page_setup setup'
checkUnexpectedReturnNULL "printSetupGetPageSetup" result
result' <- (newObject Gtk.PageSetup.PageSetup) result
touchManagedPtr setup
return result'
#if defined(ENABLE_OVERLOADING)
data PrintSetupGetPageSetupMethodInfo
instance (signature ~ (m Gtk.PageSetup.PageSetup), MonadIO m) => O.OverloadedMethod PrintSetupGetPageSetupMethodInfo PrintSetup signature where
overloadedMethod = printSetupGetPageSetup
instance O.OverloadedMethodInfo PrintSetupGetPageSetupMethodInfo PrintSetup where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PrintSetup.printSetupGetPageSetup",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PrintSetup.html#v:printSetupGetPageSetup"
})
#endif
foreign import ccall "gtk_print_setup_get_print_settings" gtk_print_setup_get_print_settings ::
Ptr PrintSetup ->
IO (Ptr Gtk.PrintSettings.PrintSettings)
printSetupGetPrintSettings ::
(B.CallStack.HasCallStack, MonadIO m) =>
PrintSetup
-> m Gtk.PrintSettings.PrintSettings
printSetupGetPrintSettings :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PrintSetup -> m PrintSettings
printSetupGetPrintSettings PrintSetup
setup = IO PrintSettings -> m PrintSettings
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintSettings -> m PrintSettings)
-> IO PrintSettings -> m PrintSettings
forall a b. (a -> b) -> a -> b
$ do
setup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
setup
result <- gtk_print_setup_get_print_settings setup'
checkUnexpectedReturnNULL "printSetupGetPrintSettings" result
result' <- (newObject Gtk.PrintSettings.PrintSettings) result
touchManagedPtr setup
return result'
#if defined(ENABLE_OVERLOADING)
data PrintSetupGetPrintSettingsMethodInfo
instance (signature ~ (m Gtk.PrintSettings.PrintSettings), MonadIO m) => O.OverloadedMethod PrintSetupGetPrintSettingsMethodInfo PrintSetup signature where
overloadedMethod = printSetupGetPrintSettings
instance O.OverloadedMethodInfo PrintSetupGetPrintSettingsMethodInfo PrintSetup where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PrintSetup.printSetupGetPrintSettings",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PrintSetup.html#v:printSetupGetPrintSettings"
})
#endif
foreign import ccall "gtk_print_setup_ref" gtk_print_setup_ref ::
Ptr PrintSetup ->
IO (Ptr PrintSetup)
printSetupRef ::
(B.CallStack.HasCallStack, MonadIO m) =>
PrintSetup
-> m PrintSetup
printSetupRef :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PrintSetup -> m PrintSetup
printSetupRef PrintSetup
setup = IO PrintSetup -> m PrintSetup
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintSetup -> m PrintSetup) -> IO PrintSetup -> m PrintSetup
forall a b. (a -> b) -> a -> b
$ do
setup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
setup
result <- gtk_print_setup_ref setup'
checkUnexpectedReturnNULL "printSetupRef" result
result' <- (wrapBoxed PrintSetup) result
touchManagedPtr setup
return result'
#if defined(ENABLE_OVERLOADING)
data PrintSetupRefMethodInfo
instance (signature ~ (m PrintSetup), MonadIO m) => O.OverloadedMethod PrintSetupRefMethodInfo PrintSetup signature where
overloadedMethod = printSetupRef
instance O.OverloadedMethodInfo PrintSetupRefMethodInfo PrintSetup where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PrintSetup.printSetupRef",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PrintSetup.html#v:printSetupRef"
})
#endif
foreign import ccall "gtk_print_setup_unref" gtk_print_setup_unref ::
Ptr PrintSetup ->
IO ()
printSetupUnref ::
(B.CallStack.HasCallStack, MonadIO m) =>
PrintSetup
-> m ()
printSetupUnref :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PrintSetup -> m ()
printSetupUnref PrintSetup
setup = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
setup' <- PrintSetup -> IO (Ptr PrintSetup)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PrintSetup
setup
gtk_print_setup_unref setup'
touchManagedPtr setup
return ()
#if defined(ENABLE_OVERLOADING)
data PrintSetupUnrefMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod PrintSetupUnrefMethodInfo PrintSetup signature where
overloadedMethod = printSetupUnref
instance O.OverloadedMethodInfo PrintSetupUnrefMethodInfo PrintSetup where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PrintSetup.printSetupUnref",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PrintSetup.html#v:printSetupUnref"
})
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolvePrintSetupMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolvePrintSetupMethod "ref" o = PrintSetupRefMethodInfo
ResolvePrintSetupMethod "unref" o = PrintSetupUnrefMethodInfo
ResolvePrintSetupMethod "getPageSetup" o = PrintSetupGetPageSetupMethodInfo
ResolvePrintSetupMethod "getPrintSettings" o = PrintSetupGetPrintSettingsMethodInfo
ResolvePrintSetupMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePrintSetupMethod t PrintSetup, O.OverloadedMethod info PrintSetup p) => OL.IsLabel t (PrintSetup -> p) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.overloadedMethod @info
#else
fromLabel _ = O.overloadedMethod @info
#endif
#if MIN_VERSION_base(4,13,0)
instance (info ~ ResolvePrintSetupMethod t PrintSetup, O.OverloadedMethod info PrintSetup p, R.HasField t PrintSetup p) => R.HasField t PrintSetup p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePrintSetupMethod t PrintSetup, O.OverloadedMethodInfo info PrintSetup) => OL.IsLabel t (O.MethodProxy info PrintSetup) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif