{-# LANGUAGE ImplicitParams, RankNTypes, TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Objects.Printer
(
Printer(..) ,
IsPrinter ,
toPrinter ,
#if defined(ENABLE_OVERLOADING)
ResolvePrinterMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PrinterAcceptsPdfMethodInfo ,
#endif
printerAcceptsPdf ,
#if defined(ENABLE_OVERLOADING)
PrinterAcceptsPsMethodInfo ,
#endif
printerAcceptsPs ,
#if defined(ENABLE_OVERLOADING)
PrinterCompareMethodInfo ,
#endif
printerCompare ,
#if defined(ENABLE_OVERLOADING)
PrinterGetBackendMethodInfo ,
#endif
printerGetBackend ,
#if defined(ENABLE_OVERLOADING)
PrinterGetCapabilitiesMethodInfo ,
#endif
printerGetCapabilities ,
#if defined(ENABLE_OVERLOADING)
PrinterGetDefaultPageSizeMethodInfo ,
#endif
printerGetDefaultPageSize ,
#if defined(ENABLE_OVERLOADING)
PrinterGetDescriptionMethodInfo ,
#endif
printerGetDescription ,
#if defined(ENABLE_OVERLOADING)
PrinterGetHardMarginsMethodInfo ,
#endif
printerGetHardMargins ,
#if defined(ENABLE_OVERLOADING)
PrinterGetHardMarginsForPaperSizeMethodInfo,
#endif
printerGetHardMarginsForPaperSize ,
#if defined(ENABLE_OVERLOADING)
PrinterGetIconNameMethodInfo ,
#endif
printerGetIconName ,
#if defined(ENABLE_OVERLOADING)
PrinterGetJobCountMethodInfo ,
#endif
printerGetJobCount ,
#if defined(ENABLE_OVERLOADING)
PrinterGetLocationMethodInfo ,
#endif
printerGetLocation ,
#if defined(ENABLE_OVERLOADING)
PrinterGetNameMethodInfo ,
#endif
printerGetName ,
#if defined(ENABLE_OVERLOADING)
PrinterGetStateMessageMethodInfo ,
#endif
printerGetStateMessage ,
#if defined(ENABLE_OVERLOADING)
PrinterHasDetailsMethodInfo ,
#endif
printerHasDetails ,
#if defined(ENABLE_OVERLOADING)
PrinterIsAcceptingJobsMethodInfo ,
#endif
printerIsAcceptingJobs ,
#if defined(ENABLE_OVERLOADING)
PrinterIsActiveMethodInfo ,
#endif
printerIsActive ,
#if defined(ENABLE_OVERLOADING)
PrinterIsDefaultMethodInfo ,
#endif
printerIsDefault ,
#if defined(ENABLE_OVERLOADING)
PrinterIsPausedMethodInfo ,
#endif
printerIsPaused ,
#if defined(ENABLE_OVERLOADING)
PrinterIsVirtualMethodInfo ,
#endif
printerIsVirtual ,
#if defined(ENABLE_OVERLOADING)
PrinterListPapersMethodInfo ,
#endif
printerListPapers ,
printerNew ,
#if defined(ENABLE_OVERLOADING)
PrinterRequestDetailsMethodInfo ,
#endif
printerRequestDetails ,
#if defined(ENABLE_OVERLOADING)
PrinterAcceptingJobsPropertyInfo ,
#endif
getPrinterAcceptingJobs ,
#if defined(ENABLE_OVERLOADING)
printerAcceptingJobs ,
#endif
#if defined(ENABLE_OVERLOADING)
PrinterAcceptsPdfPropertyInfo ,
#endif
constructPrinterAcceptsPdf ,
getPrinterAcceptsPdf ,
#if defined(ENABLE_OVERLOADING)
PrinterAcceptsPsPropertyInfo ,
#endif
constructPrinterAcceptsPs ,
getPrinterAcceptsPs ,
#if defined(ENABLE_OVERLOADING)
PrinterIconNamePropertyInfo ,
#endif
getPrinterIconName ,
#if defined(ENABLE_OVERLOADING)
printerIconName ,
#endif
#if defined(ENABLE_OVERLOADING)
PrinterIsVirtualPropertyInfo ,
#endif
constructPrinterIsVirtual ,
getPrinterIsVirtual ,
#if defined(ENABLE_OVERLOADING)
PrinterJobCountPropertyInfo ,
#endif
getPrinterJobCount ,
#if defined(ENABLE_OVERLOADING)
printerJobCount ,
#endif
#if defined(ENABLE_OVERLOADING)
PrinterLocationPropertyInfo ,
#endif
getPrinterLocation ,
#if defined(ENABLE_OVERLOADING)
printerLocation ,
#endif
#if defined(ENABLE_OVERLOADING)
PrinterNamePropertyInfo ,
#endif
constructPrinterName ,
getPrinterName ,
#if defined(ENABLE_OVERLOADING)
printerName ,
#endif
#if defined(ENABLE_OVERLOADING)
PrinterPausedPropertyInfo ,
#endif
getPrinterPaused ,
#if defined(ENABLE_OVERLOADING)
printerPaused ,
#endif
#if defined(ENABLE_OVERLOADING)
PrinterStateMessagePropertyInfo ,
#endif
getPrinterStateMessage ,
#if defined(ENABLE_OVERLOADING)
printerStateMessage ,
#endif
PrinterDetailsAcquiredCallback ,
#if defined(ENABLE_OVERLOADING)
PrinterDetailsAcquiredSignalInfo ,
#endif
afterPrinterDetailsAcquired ,
onPrinterDetailsAcquired ,
) 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 {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Structs.PaperSize as Gtk.PaperSize
import {-# SOURCE #-} qualified GI.Gtk.Structs.PrintBackend as Gtk.PrintBackend
#else
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gtk.Flags as Gtk.Flags
import {-# SOURCE #-} qualified GI.Gtk.Objects.PageSetup as Gtk.PageSetup
import {-# SOURCE #-} qualified GI.Gtk.Structs.PaperSize as Gtk.PaperSize
import {-# SOURCE #-} qualified GI.Gtk.Structs.PrintBackend as Gtk.PrintBackend
#endif
newtype Printer = Printer (SP.ManagedPtr Printer)
deriving (Printer -> Printer -> Bool
(Printer -> Printer -> Bool)
-> (Printer -> Printer -> Bool) -> Eq Printer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Printer -> Printer -> Bool
== :: Printer -> Printer -> Bool
$c/= :: Printer -> Printer -> Bool
/= :: Printer -> Printer -> Bool
Eq)
instance SP.ManagedPtrNewtype Printer where
toManagedPtr :: Printer -> ManagedPtr Printer
toManagedPtr (Printer ManagedPtr Printer
p) = ManagedPtr Printer
p
foreign import ccall "gtk_printer_get_type"
c_gtk_printer_get_type :: IO B.Types.GType
instance B.Types.TypedObject Printer where
glibType :: IO GType
glibType = IO GType
c_gtk_printer_get_type
instance B.Types.GObject Printer
class (SP.GObject o, O.IsDescendantOf Printer o) => IsPrinter o
instance (SP.GObject o, O.IsDescendantOf Printer o) => IsPrinter o
instance O.HasParentTypes Printer
type instance O.ParentTypes Printer = '[GObject.Object.Object]
toPrinter :: (MIO.MonadIO m, IsPrinter o) => o -> m Printer
toPrinter :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Printer
toPrinter = IO Printer -> m Printer
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Printer -> m Printer) -> (o -> IO Printer) -> o -> m Printer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr Printer -> Printer) -> o -> IO Printer
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr Printer -> Printer
Printer
instance B.GValue.IsGValue (Maybe Printer) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_printer_get_type
gvalueSet_ :: Ptr GValue -> Maybe Printer -> IO ()
gvalueSet_ Ptr GValue
gv Maybe Printer
P.Nothing = Ptr GValue -> Ptr Printer -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr Printer
forall a. Ptr a
FP.nullPtr :: FP.Ptr Printer)
gvalueSet_ Ptr GValue
gv (P.Just Printer
obj) = Printer -> (Ptr Printer -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr Printer
obj (Ptr GValue -> Ptr Printer -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe Printer)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr Printer)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr Printer)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newObject Printer ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolvePrinterMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolvePrinterMethod "acceptsPdf" o = PrinterAcceptsPdfMethodInfo
ResolvePrinterMethod "acceptsPs" o = PrinterAcceptsPsMethodInfo
ResolvePrinterMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolvePrinterMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolvePrinterMethod "compare" o = PrinterCompareMethodInfo
ResolvePrinterMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolvePrinterMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolvePrinterMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolvePrinterMethod "hasDetails" o = PrinterHasDetailsMethodInfo
ResolvePrinterMethod "isAcceptingJobs" o = PrinterIsAcceptingJobsMethodInfo
ResolvePrinterMethod "isActive" o = PrinterIsActiveMethodInfo
ResolvePrinterMethod "isDefault" o = PrinterIsDefaultMethodInfo
ResolvePrinterMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolvePrinterMethod "isPaused" o = PrinterIsPausedMethodInfo
ResolvePrinterMethod "isVirtual" o = PrinterIsVirtualMethodInfo
ResolvePrinterMethod "listPapers" o = PrinterListPapersMethodInfo
ResolvePrinterMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolvePrinterMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolvePrinterMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolvePrinterMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolvePrinterMethod "requestDetails" o = PrinterRequestDetailsMethodInfo
ResolvePrinterMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolvePrinterMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolvePrinterMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolvePrinterMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolvePrinterMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolvePrinterMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolvePrinterMethod "getBackend" o = PrinterGetBackendMethodInfo
ResolvePrinterMethod "getCapabilities" o = PrinterGetCapabilitiesMethodInfo
ResolvePrinterMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolvePrinterMethod "getDefaultPageSize" o = PrinterGetDefaultPageSizeMethodInfo
ResolvePrinterMethod "getDescription" o = PrinterGetDescriptionMethodInfo
ResolvePrinterMethod "getHardMargins" o = PrinterGetHardMarginsMethodInfo
ResolvePrinterMethod "getHardMarginsForPaperSize" o = PrinterGetHardMarginsForPaperSizeMethodInfo
ResolvePrinterMethod "getIconName" o = PrinterGetIconNameMethodInfo
ResolvePrinterMethod "getJobCount" o = PrinterGetJobCountMethodInfo
ResolvePrinterMethod "getLocation" o = PrinterGetLocationMethodInfo
ResolvePrinterMethod "getName" o = PrinterGetNameMethodInfo
ResolvePrinterMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolvePrinterMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolvePrinterMethod "getStateMessage" o = PrinterGetStateMessageMethodInfo
ResolvePrinterMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolvePrinterMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolvePrinterMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolvePrinterMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePrinterMethod t Printer, O.OverloadedMethod info Printer p) => OL.IsLabel t (Printer -> 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 ~ ResolvePrinterMethod t Printer, O.OverloadedMethod info Printer p, R.HasField t Printer p) => R.HasField t Printer p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePrinterMethod t Printer, O.OverloadedMethodInfo info Printer) => OL.IsLabel t (O.MethodProxy info Printer) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
type PrinterDetailsAcquiredCallback =
Bool
-> IO ()
type C_PrinterDetailsAcquiredCallback =
Ptr Printer ->
CInt ->
Ptr () ->
IO ()
foreign import ccall "wrapper"
mk_PrinterDetailsAcquiredCallback :: C_PrinterDetailsAcquiredCallback -> IO (FunPtr C_PrinterDetailsAcquiredCallback)
wrap_PrinterDetailsAcquiredCallback ::
GObject a => (a -> PrinterDetailsAcquiredCallback) ->
C_PrinterDetailsAcquiredCallback
wrap_PrinterDetailsAcquiredCallback :: forall a.
GObject a =>
(a -> PrinterDetailsAcquiredCallback)
-> C_PrinterDetailsAcquiredCallback
wrap_PrinterDetailsAcquiredCallback a -> PrinterDetailsAcquiredCallback
gi'cb Ptr Printer
gi'selfPtr CInt
success Ptr ()
_ = do
let success' :: Bool
success' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
success
Ptr Printer -> (Printer -> IO ()) -> IO ()
forall o b.
(HasCallStack, GObject o) =>
Ptr o -> (o -> IO b) -> IO b
B.ManagedPtr.withNewObject Ptr Printer
gi'selfPtr ((Printer -> IO ()) -> IO ()) -> (Printer -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Printer
gi'self -> a -> PrinterDetailsAcquiredCallback
gi'cb (Printer -> a
forall a b. Coercible a b => a -> b
Coerce.coerce Printer
gi'self) Bool
success'
onPrinterDetailsAcquired :: (IsPrinter a, MonadIO m) => a -> ((?self :: a) => PrinterDetailsAcquiredCallback) -> m SignalHandlerId
onPrinterDetailsAcquired :: forall a (m :: * -> *).
(IsPrinter a, MonadIO m) =>
a
-> ((?self::a) => PrinterDetailsAcquiredCallback)
-> m SignalHandlerId
onPrinterDetailsAcquired a
obj (?self::a) => PrinterDetailsAcquiredCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> PrinterDetailsAcquiredCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PrinterDetailsAcquiredCallback
PrinterDetailsAcquiredCallback
cb
let wrapped' :: C_PrinterDetailsAcquiredCallback
wrapped' = (a -> PrinterDetailsAcquiredCallback)
-> C_PrinterDetailsAcquiredCallback
forall a.
GObject a =>
(a -> PrinterDetailsAcquiredCallback)
-> C_PrinterDetailsAcquiredCallback
wrap_PrinterDetailsAcquiredCallback a -> PrinterDetailsAcquiredCallback
wrapped
wrapped'' <- C_PrinterDetailsAcquiredCallback
-> IO (FunPtr C_PrinterDetailsAcquiredCallback)
mk_PrinterDetailsAcquiredCallback C_PrinterDetailsAcquiredCallback
wrapped'
connectSignalFunPtr obj "details-acquired" wrapped'' SignalConnectBefore Nothing
afterPrinterDetailsAcquired :: (IsPrinter a, MonadIO m) => a -> ((?self :: a) => PrinterDetailsAcquiredCallback) -> m SignalHandlerId
afterPrinterDetailsAcquired :: forall a (m :: * -> *).
(IsPrinter a, MonadIO m) =>
a
-> ((?self::a) => PrinterDetailsAcquiredCallback)
-> m SignalHandlerId
afterPrinterDetailsAcquired a
obj (?self::a) => PrinterDetailsAcquiredCallback
cb = IO SignalHandlerId -> m SignalHandlerId
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO SignalHandlerId -> m SignalHandlerId)
-> IO SignalHandlerId -> m SignalHandlerId
forall a b. (a -> b) -> a -> b
$ do
let wrapped :: a -> PrinterDetailsAcquiredCallback
wrapped a
self = let ?self = a
?self::a
self in (?self::a) => PrinterDetailsAcquiredCallback
PrinterDetailsAcquiredCallback
cb
let wrapped' :: C_PrinterDetailsAcquiredCallback
wrapped' = (a -> PrinterDetailsAcquiredCallback)
-> C_PrinterDetailsAcquiredCallback
forall a.
GObject a =>
(a -> PrinterDetailsAcquiredCallback)
-> C_PrinterDetailsAcquiredCallback
wrap_PrinterDetailsAcquiredCallback a -> PrinterDetailsAcquiredCallback
wrapped
wrapped'' <- C_PrinterDetailsAcquiredCallback
-> IO (FunPtr C_PrinterDetailsAcquiredCallback)
mk_PrinterDetailsAcquiredCallback C_PrinterDetailsAcquiredCallback
wrapped'
connectSignalFunPtr obj "details-acquired" wrapped'' SignalConnectAfter Nothing
#if defined(ENABLE_OVERLOADING)
data PrinterDetailsAcquiredSignalInfo
instance SignalInfo PrinterDetailsAcquiredSignalInfo where
type HaskellCallbackType PrinterDetailsAcquiredSignalInfo = PrinterDetailsAcquiredCallback
connectSignal obj cb connectMode detail = do
let cb' = wrap_PrinterDetailsAcquiredCallback cb
cb'' <- mk_PrinterDetailsAcquiredCallback cb'
connectSignalFunPtr obj "details-acquired" cb'' connectMode detail
dbgSignalInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer::details-acquired"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:signal:detailsAcquired"})
#endif
getPrinterAcceptingJobs :: (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterAcceptingJobs :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterAcceptingJobs o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"accepting-jobs"
#if defined(ENABLE_OVERLOADING)
data PrinterAcceptingJobsPropertyInfo
instance AttrInfo PrinterAcceptingJobsPropertyInfo where
type AttrAllowedOps PrinterAcceptingJobsPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint PrinterAcceptingJobsPropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterAcceptingJobsPropertyInfo = (~) ()
type AttrTransferTypeConstraint PrinterAcceptingJobsPropertyInfo = (~) ()
type AttrTransferType PrinterAcceptingJobsPropertyInfo = ()
type AttrGetType PrinterAcceptingJobsPropertyInfo = Bool
type AttrLabel PrinterAcceptingJobsPropertyInfo = "accepting-jobs"
type AttrOrigin PrinterAcceptingJobsPropertyInfo = Printer
attrGet = getPrinterAcceptingJobs
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.acceptingJobs"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:acceptingJobs"
})
#endif
getPrinterAcceptsPdf :: (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterAcceptsPdf :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterAcceptsPdf o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"accepts-pdf"
constructPrinterAcceptsPdf :: (IsPrinter o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrinterAcceptsPdf :: forall o (m :: * -> *).
(IsPrinter o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrinterAcceptsPdf Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"accepts-pdf" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrinterAcceptsPdfPropertyInfo
instance AttrInfo PrinterAcceptsPdfPropertyInfo where
type AttrAllowedOps PrinterAcceptsPdfPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint PrinterAcceptsPdfPropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterAcceptsPdfPropertyInfo = (~) Bool
type AttrTransferTypeConstraint PrinterAcceptsPdfPropertyInfo = (~) Bool
type AttrTransferType PrinterAcceptsPdfPropertyInfo = Bool
type AttrGetType PrinterAcceptsPdfPropertyInfo = Bool
type AttrLabel PrinterAcceptsPdfPropertyInfo = "accepts-pdf"
type AttrOrigin PrinterAcceptsPdfPropertyInfo = Printer
attrGet = getPrinterAcceptsPdf
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructPrinterAcceptsPdf
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.acceptsPdf"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:acceptsPdf"
})
#endif
getPrinterAcceptsPs :: (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterAcceptsPs :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterAcceptsPs o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"accepts-ps"
constructPrinterAcceptsPs :: (IsPrinter o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrinterAcceptsPs :: forall o (m :: * -> *).
(IsPrinter o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrinterAcceptsPs Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"accepts-ps" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrinterAcceptsPsPropertyInfo
instance AttrInfo PrinterAcceptsPsPropertyInfo where
type AttrAllowedOps PrinterAcceptsPsPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint PrinterAcceptsPsPropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterAcceptsPsPropertyInfo = (~) Bool
type AttrTransferTypeConstraint PrinterAcceptsPsPropertyInfo = (~) Bool
type AttrTransferType PrinterAcceptsPsPropertyInfo = Bool
type AttrGetType PrinterAcceptsPsPropertyInfo = Bool
type AttrLabel PrinterAcceptsPsPropertyInfo = "accepts-ps"
type AttrOrigin PrinterAcceptsPsPropertyInfo = Printer
attrGet = getPrinterAcceptsPs
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructPrinterAcceptsPs
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.acceptsPs"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:acceptsPs"
})
#endif
getPrinterIconName :: (MonadIO m, IsPrinter o) => o -> m T.Text
getPrinterIconName :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Text
getPrinterIconName o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getPrinterIconName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"icon-name"
#if defined(ENABLE_OVERLOADING)
data PrinterIconNamePropertyInfo
instance AttrInfo PrinterIconNamePropertyInfo where
type AttrAllowedOps PrinterIconNamePropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint PrinterIconNamePropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterIconNamePropertyInfo = (~) ()
type AttrTransferTypeConstraint PrinterIconNamePropertyInfo = (~) ()
type AttrTransferType PrinterIconNamePropertyInfo = ()
type AttrGetType PrinterIconNamePropertyInfo = T.Text
type AttrLabel PrinterIconNamePropertyInfo = "icon-name"
type AttrOrigin PrinterIconNamePropertyInfo = Printer
attrGet = getPrinterIconName
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.iconName"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:iconName"
})
#endif
getPrinterIsVirtual :: (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterIsVirtual :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterIsVirtual o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"is-virtual"
constructPrinterIsVirtual :: (IsPrinter o, MIO.MonadIO m) => Bool -> m (GValueConstruct o)
constructPrinterIsVirtual :: forall o (m :: * -> *).
(IsPrinter o, MonadIO m) =>
Bool -> m (GValueConstruct o)
constructPrinterIsVirtual Bool
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Bool -> IO (GValueConstruct o)
forall o. String -> Bool -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBool String
"is-virtual" Bool
val
#if defined(ENABLE_OVERLOADING)
data PrinterIsVirtualPropertyInfo
instance AttrInfo PrinterIsVirtualPropertyInfo where
type AttrAllowedOps PrinterIsVirtualPropertyInfo = '[ 'AttrConstruct, 'AttrGet]
type AttrBaseTypeConstraint PrinterIsVirtualPropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterIsVirtualPropertyInfo = (~) Bool
type AttrTransferTypeConstraint PrinterIsVirtualPropertyInfo = (~) Bool
type AttrTransferType PrinterIsVirtualPropertyInfo = Bool
type AttrGetType PrinterIsVirtualPropertyInfo = Bool
type AttrLabel PrinterIsVirtualPropertyInfo = "is-virtual"
type AttrOrigin PrinterIsVirtualPropertyInfo = Printer
attrGet = getPrinterIsVirtual
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructPrinterIsVirtual
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.isVirtual"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:isVirtual"
})
#endif
getPrinterJobCount :: (MonadIO m, IsPrinter o) => o -> m Int32
getPrinterJobCount :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Int32
getPrinterJobCount o
obj = IO Int32 -> m Int32
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Int32 -> m Int32) -> IO Int32 -> m Int32
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Int32
forall a. GObject a => a -> String -> IO Int32
B.Properties.getObjectPropertyInt32 o
obj String
"job-count"
#if defined(ENABLE_OVERLOADING)
data PrinterJobCountPropertyInfo
instance AttrInfo PrinterJobCountPropertyInfo where
type AttrAllowedOps PrinterJobCountPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint PrinterJobCountPropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterJobCountPropertyInfo = (~) ()
type AttrTransferTypeConstraint PrinterJobCountPropertyInfo = (~) ()
type AttrTransferType PrinterJobCountPropertyInfo = ()
type AttrGetType PrinterJobCountPropertyInfo = Int32
type AttrLabel PrinterJobCountPropertyInfo = "job-count"
type AttrOrigin PrinterJobCountPropertyInfo = Printer
attrGet = getPrinterJobCount
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.jobCount"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:jobCount"
})
#endif
getPrinterLocation :: (MonadIO m, IsPrinter o) => o -> m T.Text
getPrinterLocation :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Text
getPrinterLocation o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getPrinterLocation" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"location"
#if defined(ENABLE_OVERLOADING)
data PrinterLocationPropertyInfo
instance AttrInfo PrinterLocationPropertyInfo where
type AttrAllowedOps PrinterLocationPropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint PrinterLocationPropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterLocationPropertyInfo = (~) ()
type AttrTransferTypeConstraint PrinterLocationPropertyInfo = (~) ()
type AttrTransferType PrinterLocationPropertyInfo = ()
type AttrGetType PrinterLocationPropertyInfo = T.Text
type AttrLabel PrinterLocationPropertyInfo = "location"
type AttrOrigin PrinterLocationPropertyInfo = Printer
attrGet = getPrinterLocation
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.location"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:location"
})
#endif
getPrinterName :: (MonadIO m, IsPrinter o) => o -> m T.Text
getPrinterName :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Text
getPrinterName o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getPrinterName" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"name"
constructPrinterName :: (IsPrinter o, MIO.MonadIO m) => T.Text -> m (GValueConstruct o)
constructPrinterName :: forall o (m :: * -> *).
(IsPrinter o, MonadIO m) =>
Text -> m (GValueConstruct o)
constructPrinterName Text
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a. IO a -> IO a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe Text -> IO (GValueConstruct o)
forall o. String -> Maybe Text -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyString String
"name" (Text -> Maybe Text
forall a. a -> Maybe a
P.Just Text
val)
#if defined(ENABLE_OVERLOADING)
data PrinterNamePropertyInfo
instance AttrInfo PrinterNamePropertyInfo where
type AttrAllowedOps PrinterNamePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint PrinterNamePropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterNamePropertyInfo = (~) T.Text
type AttrTransferTypeConstraint PrinterNamePropertyInfo = (~) T.Text
type AttrTransferType PrinterNamePropertyInfo = T.Text
type AttrGetType PrinterNamePropertyInfo = T.Text
type AttrLabel PrinterNamePropertyInfo = "name"
type AttrOrigin PrinterNamePropertyInfo = Printer
attrGet = getPrinterName
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructPrinterName
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.name"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:name"
})
#endif
getPrinterPaused :: (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterPaused :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Bool
getPrinterPaused o
obj = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ o -> String -> IO Bool
forall a. GObject a => a -> String -> IO Bool
B.Properties.getObjectPropertyBool o
obj String
"paused"
#if defined(ENABLE_OVERLOADING)
data PrinterPausedPropertyInfo
instance AttrInfo PrinterPausedPropertyInfo where
type AttrAllowedOps PrinterPausedPropertyInfo = '[ 'AttrGet]
type AttrBaseTypeConstraint PrinterPausedPropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterPausedPropertyInfo = (~) ()
type AttrTransferTypeConstraint PrinterPausedPropertyInfo = (~) ()
type AttrTransferType PrinterPausedPropertyInfo = ()
type AttrGetType PrinterPausedPropertyInfo = Bool
type AttrLabel PrinterPausedPropertyInfo = "paused"
type AttrOrigin PrinterPausedPropertyInfo = Printer
attrGet = getPrinterPaused
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.paused"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:paused"
})
#endif
getPrinterStateMessage :: (MonadIO m, IsPrinter o) => o -> m T.Text
getPrinterStateMessage :: forall (m :: * -> *) o. (MonadIO m, IsPrinter o) => o -> m Text
getPrinterStateMessage o
obj = IO Text -> m Text
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Text -> m Text) -> IO Text -> m Text
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Text) -> IO Text
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getPrinterStateMessage" (IO (Maybe Text) -> IO Text) -> IO (Maybe Text) -> IO Text
forall a b. (a -> b) -> a -> b
$ o -> String -> IO (Maybe Text)
forall a. GObject a => a -> String -> IO (Maybe Text)
B.Properties.getObjectPropertyString o
obj String
"state-message"
#if defined(ENABLE_OVERLOADING)
data PrinterStateMessagePropertyInfo
instance AttrInfo PrinterStateMessagePropertyInfo where
type AttrAllowedOps PrinterStateMessagePropertyInfo = '[ 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint PrinterStateMessagePropertyInfo = IsPrinter
type AttrSetTypeConstraint PrinterStateMessagePropertyInfo = (~) ()
type AttrTransferTypeConstraint PrinterStateMessagePropertyInfo = (~) ()
type AttrTransferType PrinterStateMessagePropertyInfo = ()
type AttrGetType PrinterStateMessagePropertyInfo = T.Text
type AttrLabel PrinterStateMessagePropertyInfo = "state-message"
type AttrOrigin PrinterStateMessagePropertyInfo = Printer
attrGet = getPrinterStateMessage
attrSet = undefined
attrTransfer _ = undefined
attrConstruct = undefined
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.stateMessage"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#g:attr:stateMessage"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList Printer
type instance O.AttributeList Printer = PrinterAttributeList
type PrinterAttributeList = ('[ '("acceptingJobs", PrinterAcceptingJobsPropertyInfo), '("acceptsPdf", PrinterAcceptsPdfPropertyInfo), '("acceptsPs", PrinterAcceptsPsPropertyInfo), '("iconName", PrinterIconNamePropertyInfo), '("isVirtual", PrinterIsVirtualPropertyInfo), '("jobCount", PrinterJobCountPropertyInfo), '("location", PrinterLocationPropertyInfo), '("name", PrinterNamePropertyInfo), '("paused", PrinterPausedPropertyInfo), '("stateMessage", PrinterStateMessagePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
printerAcceptingJobs :: AttrLabelProxy "acceptingJobs"
printerAcceptingJobs = AttrLabelProxy
printerIconName :: AttrLabelProxy "iconName"
printerIconName = AttrLabelProxy
printerJobCount :: AttrLabelProxy "jobCount"
printerJobCount = AttrLabelProxy
printerLocation :: AttrLabelProxy "location"
printerLocation = AttrLabelProxy
printerName :: AttrLabelProxy "name"
printerName = AttrLabelProxy
printerPaused :: AttrLabelProxy "paused"
printerPaused = AttrLabelProxy
printerStateMessage :: AttrLabelProxy "stateMessage"
printerStateMessage = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList Printer = PrinterSignalList
type PrinterSignalList = ('[ '("detailsAcquired", PrinterDetailsAcquiredSignalInfo), '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_printer_new" gtk_printer_new ::
CString ->
Ptr Gtk.PrintBackend.PrintBackend ->
CInt ->
IO (Ptr Printer)
printerNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Gtk.PrintBackend.PrintBackend
-> Bool
-> m Printer
printerNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> PrintBackend -> Bool -> m Printer
printerNew Text
name PrintBackend
backend Bool
virtual_ = IO Printer -> m Printer
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Printer -> m Printer) -> IO Printer -> m Printer
forall a b. (a -> b) -> a -> b
$ do
name' <- Text -> IO CString
textToCString Text
name
backend' <- unsafeManagedPtrGetPtr backend
let virtual_' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.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
P.fromEnum) Bool
virtual_
result <- gtk_printer_new name' backend' virtual_'
checkUnexpectedReturnNULL "printerNew" result
result' <- (wrapObject Printer) result
touchManagedPtr backend
freeMem name'
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_printer_accepts_pdf" gtk_printer_accepts_pdf ::
Ptr Printer ->
IO CInt
printerAcceptsPdf ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Bool
printerAcceptsPdf :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Bool
printerAcceptsPdf a
printer = IO Bool -> m Bool
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_accepts_pdf printer'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterAcceptsPdfMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterAcceptsPdfMethodInfo a signature where
overloadedMethod = printerAcceptsPdf
instance O.OverloadedMethodInfo PrinterAcceptsPdfMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerAcceptsPdf",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerAcceptsPdf"
})
#endif
foreign import ccall "gtk_printer_accepts_ps" gtk_printer_accepts_ps ::
Ptr Printer ->
IO CInt
printerAcceptsPs ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Bool
printerAcceptsPs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Bool
printerAcceptsPs a
printer = IO Bool -> m Bool
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_accepts_ps printer'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterAcceptsPsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterAcceptsPsMethodInfo a signature where
overloadedMethod = printerAcceptsPs
instance O.OverloadedMethodInfo PrinterAcceptsPsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerAcceptsPs",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerAcceptsPs"
})
#endif
foreign import ccall "gtk_printer_compare" gtk_printer_compare ::
Ptr Printer ->
Ptr Printer ->
IO Int32
printerCompare ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a, IsPrinter b) =>
a
-> b
-> m Int32
printerCompare :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsPrinter a, IsPrinter b) =>
a -> b -> m Int32
printerCompare a
a b
b = IO Int32 -> m Int32
forall a. IO a -> m a
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
a' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
a
b' <- unsafeManagedPtrCastPtr b
result <- gtk_printer_compare a' b'
touchManagedPtr a
touchManagedPtr b
return result
#if defined(ENABLE_OVERLOADING)
data PrinterCompareMethodInfo
instance (signature ~ (b -> m Int32), MonadIO m, IsPrinter a, IsPrinter b) => O.OverloadedMethod PrinterCompareMethodInfo a signature where
overloadedMethod = printerCompare
instance O.OverloadedMethodInfo PrinterCompareMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerCompare",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerCompare"
})
#endif
foreign import ccall "gtk_printer_get_backend" gtk_printer_get_backend ::
Ptr Printer ->
IO (Ptr Gtk.PrintBackend.PrintBackend)
printerGetBackend ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Gtk.PrintBackend.PrintBackend
printerGetBackend :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m PrintBackend
printerGetBackend a
printer = IO PrintBackend -> m PrintBackend
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO PrintBackend -> m PrintBackend)
-> IO PrintBackend -> m PrintBackend
forall a b. (a -> b) -> a -> b
$ do
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_get_backend printer'
checkUnexpectedReturnNULL "printerGetBackend" result
result' <- (newPtr Gtk.PrintBackend.PrintBackend) result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterGetBackendMethodInfo
instance (signature ~ (m Gtk.PrintBackend.PrintBackend), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetBackendMethodInfo a signature where
overloadedMethod = printerGetBackend
instance O.OverloadedMethodInfo PrinterGetBackendMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetBackend",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetBackend"
})
#endif
foreign import ccall "gtk_printer_get_capabilities" gtk_printer_get_capabilities ::
Ptr Printer ->
IO CUInt
printerGetCapabilities ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m [Gtk.Flags.PrintCapabilities]
printerGetCapabilities :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m [PrintCapabilities]
printerGetCapabilities a
printer = IO [PrintCapabilities] -> m [PrintCapabilities]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [PrintCapabilities] -> m [PrintCapabilities])
-> IO [PrintCapabilities] -> m [PrintCapabilities]
forall a b. (a -> b) -> a -> b
$ do
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_get_capabilities printer'
let result' = CUInt -> [PrintCapabilities]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterGetCapabilitiesMethodInfo
instance (signature ~ (m [Gtk.Flags.PrintCapabilities]), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetCapabilitiesMethodInfo a signature where
overloadedMethod = printerGetCapabilities
instance O.OverloadedMethodInfo PrinterGetCapabilitiesMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetCapabilities",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetCapabilities"
})
#endif
foreign import ccall "gtk_printer_get_default_page_size" gtk_printer_get_default_page_size ::
Ptr Printer ->
IO (Ptr Gtk.PageSetup.PageSetup)
printerGetDefaultPageSize ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Gtk.PageSetup.PageSetup
printerGetDefaultPageSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m PageSetup
printerGetDefaultPageSize a
printer = 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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_get_default_page_size printer'
checkUnexpectedReturnNULL "printerGetDefaultPageSize" result
result' <- (wrapObject Gtk.PageSetup.PageSetup) result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterGetDefaultPageSizeMethodInfo
instance (signature ~ (m Gtk.PageSetup.PageSetup), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetDefaultPageSizeMethodInfo a signature where
overloadedMethod = printerGetDefaultPageSize
instance O.OverloadedMethodInfo PrinterGetDefaultPageSizeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetDefaultPageSize",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetDefaultPageSize"
})
#endif
foreign import ccall "gtk_printer_get_description" gtk_printer_get_description ::
Ptr Printer ->
IO CString
printerGetDescription ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m T.Text
printerGetDescription :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Text
printerGetDescription a
printer = IO Text -> m Text
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_get_description printer'
checkUnexpectedReturnNULL "printerGetDescription" result
result' <- cstringToText result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterGetDescriptionMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetDescriptionMethodInfo a signature where
overloadedMethod = printerGetDescription
instance O.OverloadedMethodInfo PrinterGetDescriptionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetDescription",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetDescription"
})
#endif
foreign import ccall "gtk_printer_get_hard_margins" gtk_printer_get_hard_margins ::
Ptr Printer ->
Ptr CDouble ->
Ptr CDouble ->
Ptr CDouble ->
Ptr CDouble ->
IO CInt
printerGetHardMargins ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m ((Bool, Double, Double, Double, Double))
printerGetHardMargins :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m (Bool, Double, Double, Double, Double)
printerGetHardMargins a
printer = IO (Bool, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double))
-> IO (Bool, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double)
forall a b. (a -> b) -> a -> b
$ do
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
top <- allocMem :: IO (Ptr CDouble)
bottom <- allocMem :: IO (Ptr CDouble)
left <- allocMem :: IO (Ptr CDouble)
right <- allocMem :: IO (Ptr CDouble)
result <- gtk_printer_get_hard_margins printer' top bottom left right
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
top' <- peek top
let top'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
top'
bottom' <- peek bottom
let bottom'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
bottom'
left' <- peek left
let left'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
left'
right' <- peek right
let right'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
right'
touchManagedPtr printer
freeMem top
freeMem bottom
freeMem left
freeMem right
return (result', top'', bottom'', left'', right'')
#if defined(ENABLE_OVERLOADING)
data PrinterGetHardMarginsMethodInfo
instance (signature ~ (m ((Bool, Double, Double, Double, Double))), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetHardMarginsMethodInfo a signature where
overloadedMethod = printerGetHardMargins
instance O.OverloadedMethodInfo PrinterGetHardMarginsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetHardMargins",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetHardMargins"
})
#endif
foreign import ccall "gtk_printer_get_hard_margins_for_paper_size" gtk_printer_get_hard_margins_for_paper_size ::
Ptr Printer ->
Ptr Gtk.PaperSize.PaperSize ->
Ptr CDouble ->
Ptr CDouble ->
Ptr CDouble ->
Ptr CDouble ->
IO CInt
printerGetHardMarginsForPaperSize ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> Gtk.PaperSize.PaperSize
-> m ((Bool, Double, Double, Double, Double))
printerGetHardMarginsForPaperSize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> PaperSize -> m (Bool, Double, Double, Double, Double)
printerGetHardMarginsForPaperSize a
printer PaperSize
paperSize = IO (Bool, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Bool, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double))
-> IO (Bool, Double, Double, Double, Double)
-> m (Bool, Double, Double, Double, Double)
forall a b. (a -> b) -> a -> b
$ do
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
paperSize' <- unsafeManagedPtrGetPtr paperSize
top <- allocMem :: IO (Ptr CDouble)
bottom <- allocMem :: IO (Ptr CDouble)
left <- allocMem :: IO (Ptr CDouble)
right <- allocMem :: IO (Ptr CDouble)
result <- gtk_printer_get_hard_margins_for_paper_size printer' paperSize' top bottom left right
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
top' <- peek top
let top'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
top'
bottom' <- peek bottom
let bottom'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
bottom'
left' <- peek left
let left'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
left'
right' <- peek right
let right'' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
right'
touchManagedPtr printer
touchManagedPtr paperSize
freeMem top
freeMem bottom
freeMem left
freeMem right
return (result', top'', bottom'', left'', right'')
#if defined(ENABLE_OVERLOADING)
data PrinterGetHardMarginsForPaperSizeMethodInfo
instance (signature ~ (Gtk.PaperSize.PaperSize -> m ((Bool, Double, Double, Double, Double))), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetHardMarginsForPaperSizeMethodInfo a signature where
overloadedMethod = printerGetHardMarginsForPaperSize
instance O.OverloadedMethodInfo PrinterGetHardMarginsForPaperSizeMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetHardMarginsForPaperSize",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetHardMarginsForPaperSize"
})
#endif
foreign import ccall "gtk_printer_get_icon_name" gtk_printer_get_icon_name ::
Ptr Printer ->
IO CString
printerGetIconName ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m T.Text
printerGetIconName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Text
printerGetIconName a
printer = IO Text -> m Text
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_get_icon_name printer'
checkUnexpectedReturnNULL "printerGetIconName" result
result' <- cstringToText result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterGetIconNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetIconNameMethodInfo a signature where
overloadedMethod = printerGetIconName
instance O.OverloadedMethodInfo PrinterGetIconNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetIconName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetIconName"
})
#endif
foreign import ccall "gtk_printer_get_job_count" gtk_printer_get_job_count ::
Ptr Printer ->
IO Int32
printerGetJobCount ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Int32
printerGetJobCount :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Int32
printerGetJobCount a
printer = IO Int32 -> m Int32
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_get_job_count printer'
touchManagedPtr printer
return result
#if defined(ENABLE_OVERLOADING)
data PrinterGetJobCountMethodInfo
instance (signature ~ (m Int32), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetJobCountMethodInfo a signature where
overloadedMethod = printerGetJobCount
instance O.OverloadedMethodInfo PrinterGetJobCountMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetJobCount",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetJobCount"
})
#endif
foreign import ccall "gtk_printer_get_location" gtk_printer_get_location ::
Ptr Printer ->
IO CString
printerGetLocation ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m T.Text
printerGetLocation :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Text
printerGetLocation a
printer = IO Text -> m Text
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_get_location printer'
checkUnexpectedReturnNULL "printerGetLocation" result
result' <- cstringToText result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterGetLocationMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetLocationMethodInfo a signature where
overloadedMethod = printerGetLocation
instance O.OverloadedMethodInfo PrinterGetLocationMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetLocation",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetLocation"
})
#endif
foreign import ccall "gtk_printer_get_name" gtk_printer_get_name ::
Ptr Printer ->
IO CString
printerGetName ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m T.Text
printerGetName :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Text
printerGetName a
printer = IO Text -> m Text
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_get_name printer'
checkUnexpectedReturnNULL "printerGetName" result
result' <- cstringToText result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetNameMethodInfo a signature where
overloadedMethod = printerGetName
instance O.OverloadedMethodInfo PrinterGetNameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetName"
})
#endif
foreign import ccall "gtk_printer_get_state_message" gtk_printer_get_state_message ::
Ptr Printer ->
IO CString
printerGetStateMessage ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m T.Text
printerGetStateMessage :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Text
printerGetStateMessage a
printer = IO Text -> m Text
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_get_state_message printer'
checkUnexpectedReturnNULL "printerGetStateMessage" result
result' <- cstringToText result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterGetStateMessageMethodInfo
instance (signature ~ (m T.Text), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterGetStateMessageMethodInfo a signature where
overloadedMethod = printerGetStateMessage
instance O.OverloadedMethodInfo PrinterGetStateMessageMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerGetStateMessage",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerGetStateMessage"
})
#endif
foreign import ccall "gtk_printer_has_details" gtk_printer_has_details ::
Ptr Printer ->
IO CInt
printerHasDetails ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Bool
printerHasDetails :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Bool
printerHasDetails a
printer = IO Bool -> m Bool
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_has_details printer'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterHasDetailsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterHasDetailsMethodInfo a signature where
overloadedMethod = printerHasDetails
instance O.OverloadedMethodInfo PrinterHasDetailsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerHasDetails",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerHasDetails"
})
#endif
foreign import ccall "gtk_printer_is_accepting_jobs" gtk_printer_is_accepting_jobs ::
Ptr Printer ->
IO CInt
printerIsAcceptingJobs ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Bool
printerIsAcceptingJobs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Bool
printerIsAcceptingJobs a
printer = IO Bool -> m Bool
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_is_accepting_jobs printer'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterIsAcceptingJobsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterIsAcceptingJobsMethodInfo a signature where
overloadedMethod = printerIsAcceptingJobs
instance O.OverloadedMethodInfo PrinterIsAcceptingJobsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerIsAcceptingJobs",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerIsAcceptingJobs"
})
#endif
foreign import ccall "gtk_printer_is_active" gtk_printer_is_active ::
Ptr Printer ->
IO CInt
printerIsActive ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Bool
printerIsActive :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Bool
printerIsActive a
printer = IO Bool -> m Bool
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_is_active printer'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterIsActiveMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterIsActiveMethodInfo a signature where
overloadedMethod = printerIsActive
instance O.OverloadedMethodInfo PrinterIsActiveMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerIsActive",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerIsActive"
})
#endif
foreign import ccall "gtk_printer_is_default" gtk_printer_is_default ::
Ptr Printer ->
IO CInt
printerIsDefault ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Bool
printerIsDefault :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Bool
printerIsDefault a
printer = IO Bool -> m Bool
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_is_default printer'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterIsDefaultMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterIsDefaultMethodInfo a signature where
overloadedMethod = printerIsDefault
instance O.OverloadedMethodInfo PrinterIsDefaultMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerIsDefault",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerIsDefault"
})
#endif
foreign import ccall "gtk_printer_is_paused" gtk_printer_is_paused ::
Ptr Printer ->
IO CInt
printerIsPaused ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Bool
printerIsPaused :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Bool
printerIsPaused a
printer = IO Bool -> m Bool
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_is_paused printer'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterIsPausedMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterIsPausedMethodInfo a signature where
overloadedMethod = printerIsPaused
instance O.OverloadedMethodInfo PrinterIsPausedMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerIsPaused",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerIsPaused"
})
#endif
foreign import ccall "gtk_printer_is_virtual" gtk_printer_is_virtual ::
Ptr Printer ->
IO CInt
printerIsVirtual ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m Bool
printerIsVirtual :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m Bool
printerIsVirtual a
printer = IO Bool -> m Bool
forall a. IO a -> m a
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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_is_virtual printer'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr printer
return result'
#if defined(ENABLE_OVERLOADING)
data PrinterIsVirtualMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterIsVirtualMethodInfo a signature where
overloadedMethod = printerIsVirtual
instance O.OverloadedMethodInfo PrinterIsVirtualMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerIsVirtual",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerIsVirtual"
})
#endif
foreign import ccall "gtk_printer_list_papers" gtk_printer_list_papers ::
Ptr Printer ->
IO (Ptr (GList (Ptr Gtk.PageSetup.PageSetup)))
printerListPapers ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m [Gtk.PageSetup.PageSetup]
printerListPapers :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m [PageSetup]
printerListPapers a
printer = 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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
result <- gtk_printer_list_papers printer'
result' <- unpackGList result
result'' <- mapM (wrapObject Gtk.PageSetup.PageSetup) result'
g_list_free result
touchManagedPtr printer
return result''
#if defined(ENABLE_OVERLOADING)
data PrinterListPapersMethodInfo
instance (signature ~ (m [Gtk.PageSetup.PageSetup]), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterListPapersMethodInfo a signature where
overloadedMethod = printerListPapers
instance O.OverloadedMethodInfo PrinterListPapersMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerListPapers",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerListPapers"
})
#endif
foreign import ccall "gtk_printer_request_details" gtk_printer_request_details ::
Ptr Printer ->
IO ()
printerRequestDetails ::
(B.CallStack.HasCallStack, MonadIO m, IsPrinter a) =>
a
-> m ()
printerRequestDetails :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsPrinter a) =>
a -> m ()
printerRequestDetails a
printer = 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
printer' <- a -> IO (Ptr Printer)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
printer
gtk_printer_request_details printer'
touchManagedPtr printer
return ()
#if defined(ENABLE_OVERLOADING)
data PrinterRequestDetailsMethodInfo
instance (signature ~ (m ()), MonadIO m, IsPrinter a) => O.OverloadedMethod PrinterRequestDetailsMethodInfo a signature where
overloadedMethod = printerRequestDetails
instance O.OverloadedMethodInfo PrinterRequestDetailsMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Objects.Printer.printerRequestDetails",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Objects-Printer.html#v:printerRequestDetails"
})
#endif