{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gtk.Structs.PaperSize
(
PaperSize(..) ,
#if defined(ENABLE_OVERLOADING)
ResolvePaperSizeMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
PaperSizeCopyMethodInfo ,
#endif
paperSizeCopy ,
#if defined(ENABLE_OVERLOADING)
PaperSizeFreeMethodInfo ,
#endif
paperSizeFree ,
paperSizeGetDefault ,
#if defined(ENABLE_OVERLOADING)
PaperSizeGetDefaultBottomMarginMethodInfo,
#endif
paperSizeGetDefaultBottomMargin ,
#if defined(ENABLE_OVERLOADING)
PaperSizeGetDefaultLeftMarginMethodInfo ,
#endif
paperSizeGetDefaultLeftMargin ,
#if defined(ENABLE_OVERLOADING)
PaperSizeGetDefaultRightMarginMethodInfo,
#endif
paperSizeGetDefaultRightMargin ,
#if defined(ENABLE_OVERLOADING)
PaperSizeGetDefaultTopMarginMethodInfo ,
#endif
paperSizeGetDefaultTopMargin ,
#if defined(ENABLE_OVERLOADING)
PaperSizeGetDisplayNameMethodInfo ,
#endif
paperSizeGetDisplayName ,
#if defined(ENABLE_OVERLOADING)
PaperSizeGetHeightMethodInfo ,
#endif
paperSizeGetHeight ,
#if defined(ENABLE_OVERLOADING)
PaperSizeGetNameMethodInfo ,
#endif
paperSizeGetName ,
paperSizeGetPaperSizes ,
#if defined(ENABLE_OVERLOADING)
PaperSizeGetPpdNameMethodInfo ,
#endif
paperSizeGetPpdName ,
#if defined(ENABLE_OVERLOADING)
PaperSizeGetWidthMethodInfo ,
#endif
paperSizeGetWidth ,
#if defined(ENABLE_OVERLOADING)
PaperSizeIsCustomMethodInfo ,
#endif
paperSizeIsCustom ,
#if defined(ENABLE_OVERLOADING)
PaperSizeIsEqualMethodInfo ,
#endif
paperSizeIsEqual ,
#if defined(ENABLE_OVERLOADING)
PaperSizeIsIppMethodInfo ,
#endif
paperSizeIsIpp ,
paperSizeNew ,
paperSizeNewCustom ,
paperSizeNewFromGvariant ,
paperSizeNewFromIpp ,
paperSizeNewFromKeyFile ,
paperSizeNewFromPpd ,
#if defined(ENABLE_OVERLOADING)
PaperSizeSetSizeMethodInfo ,
#endif
paperSizeSetSize ,
#if defined(ENABLE_OVERLOADING)
PaperSizeToGvariantMethodInfo ,
#endif
paperSizeToGvariant ,
#if defined(ENABLE_OVERLOADING)
PaperSizeToKeyFileMethodInfo ,
#endif
paperSizeToKeyFile ,
) 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 {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
#else
import qualified GI.GLib.Structs.KeyFile as GLib.KeyFile
import {-# SOURCE #-} qualified GI.Gtk.Enums as Gtk.Enums
#endif
newtype PaperSize = PaperSize (SP.ManagedPtr PaperSize)
deriving (PaperSize -> PaperSize -> Bool
(PaperSize -> PaperSize -> Bool)
-> (PaperSize -> PaperSize -> Bool) -> Eq PaperSize
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PaperSize -> PaperSize -> Bool
== :: PaperSize -> PaperSize -> Bool
$c/= :: PaperSize -> PaperSize -> Bool
/= :: PaperSize -> PaperSize -> Bool
Eq)
instance SP.ManagedPtrNewtype PaperSize where
toManagedPtr :: PaperSize -> ManagedPtr PaperSize
toManagedPtr (PaperSize ManagedPtr PaperSize
p) = ManagedPtr PaperSize
p
foreign import ccall "gtk_paper_size_get_type" c_gtk_paper_size_get_type ::
IO GType
type instance O.ParentTypes PaperSize = '[]
instance O.HasParentTypes PaperSize
instance B.Types.TypedObject PaperSize where
glibType :: IO GType
glibType = IO GType
c_gtk_paper_size_get_type
instance B.Types.GBoxed PaperSize
instance B.GValue.IsGValue (Maybe PaperSize) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gtk_paper_size_get_type
gvalueSet_ :: Ptr GValue -> Maybe PaperSize -> IO ()
gvalueSet_ Ptr GValue
gv Maybe PaperSize
P.Nothing = Ptr GValue -> Ptr PaperSize -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv (Ptr PaperSize
forall a. Ptr a
FP.nullPtr :: FP.Ptr PaperSize)
gvalueSet_ Ptr GValue
gv (P.Just PaperSize
obj) = PaperSize -> (Ptr PaperSize -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr PaperSize
obj (Ptr GValue -> Ptr PaperSize -> IO ()
forall a. Ptr GValue -> Ptr a -> IO ()
B.GValue.set_boxed Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe PaperSize)
gvalueGet_ Ptr GValue
gv = do
ptr <- Ptr GValue -> IO (Ptr PaperSize)
forall b. Ptr GValue -> IO (Ptr b)
B.GValue.get_boxed Ptr GValue
gv :: IO (Ptr PaperSize)
if ptr /= FP.nullPtr
then P.Just <$> B.ManagedPtr.newBoxed PaperSize ptr
else return P.Nothing
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList PaperSize
type instance O.AttributeList PaperSize = PaperSizeAttributeList
type PaperSizeAttributeList = ('[ ] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gtk_paper_size_new" gtk_paper_size_new ::
CString ->
IO (Ptr PaperSize)
paperSizeNew ::
(B.CallStack.HasCallStack, MonadIO m) =>
Maybe (T.Text)
-> m PaperSize
paperSizeNew :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Maybe Text -> m PaperSize
paperSizeNew Maybe Text
name = IO PaperSize -> m PaperSize
forall a. IO a -> m a
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
maybeName <- case Maybe Text
name of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
Just Text
jName -> do
jName' <- Text -> IO (Ptr CChar)
textToCString Text
jName
return jName'
result <- gtk_paper_size_new maybeName
checkUnexpectedReturnNULL "paperSizeNew" result
result' <- (wrapBoxed PaperSize) result
freeMem maybeName
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_paper_size_new_custom" gtk_paper_size_new_custom ::
CString ->
CString ->
CDouble ->
CDouble ->
CUInt ->
IO (Ptr PaperSize)
paperSizeNewCustom ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> T.Text
-> Double
-> Double
-> Gtk.Enums.Unit
-> m PaperSize
paperSizeNewCustom :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Text -> Double -> Double -> Unit -> m PaperSize
paperSizeNewCustom Text
name Text
displayName Double
width Double
height Unit
unit = IO PaperSize -> m PaperSize
forall a. IO a -> m a
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
name' <- Text -> IO (Ptr CChar)
textToCString Text
name
displayName' <- textToCString displayName
let width' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
width
let height' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
height
let 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
result <- gtk_paper_size_new_custom name' displayName' width' height' unit'
checkUnexpectedReturnNULL "paperSizeNewCustom" result
result' <- (wrapBoxed PaperSize) result
freeMem name'
freeMem displayName'
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_paper_size_new_from_gvariant" gtk_paper_size_new_from_gvariant ::
Ptr GVariant ->
IO (Ptr PaperSize)
paperSizeNewFromGvariant ::
(B.CallStack.HasCallStack, MonadIO m) =>
GVariant
-> m PaperSize
paperSizeNewFromGvariant :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
GVariant -> m PaperSize
paperSizeNewFromGvariant GVariant
variant = IO PaperSize -> m PaperSize
forall a. IO a -> m a
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
variant' <- GVariant -> IO (Ptr GVariant)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr GVariant
variant
result <- gtk_paper_size_new_from_gvariant variant'
checkUnexpectedReturnNULL "paperSizeNewFromGvariant" result
result' <- (wrapBoxed PaperSize) result
touchManagedPtr variant
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_paper_size_new_from_ipp" gtk_paper_size_new_from_ipp ::
CString ->
CDouble ->
CDouble ->
IO (Ptr PaperSize)
paperSizeNewFromIpp ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> Double
-> Double
-> m PaperSize
paperSizeNewFromIpp :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Double -> Double -> m PaperSize
paperSizeNewFromIpp Text
ippName Double
width Double
height = IO PaperSize -> m PaperSize
forall a. IO a -> m a
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
ippName' <- Text -> IO (Ptr CChar)
textToCString Text
ippName
let width' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
width
let height' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
height
result <- gtk_paper_size_new_from_ipp ippName' width' height'
checkUnexpectedReturnNULL "paperSizeNewFromIpp" result
result' <- (wrapBoxed PaperSize) result
freeMem ippName'
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_paper_size_new_from_key_file" gtk_paper_size_new_from_key_file ::
Ptr GLib.KeyFile.KeyFile ->
CString ->
Ptr (Ptr GError) ->
IO (Ptr PaperSize)
paperSizeNewFromKeyFile ::
(B.CallStack.HasCallStack, MonadIO m) =>
GLib.KeyFile.KeyFile
-> Maybe (T.Text)
-> m PaperSize
paperSizeNewFromKeyFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
KeyFile -> Maybe Text -> m PaperSize
paperSizeNewFromKeyFile KeyFile
keyFile Maybe Text
groupName = IO PaperSize -> m PaperSize
forall a. IO a -> m a
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
keyFile' <- KeyFile -> IO (Ptr KeyFile)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr KeyFile
keyFile
maybeGroupName <- case groupName of
Maybe Text
Nothing -> Ptr CChar -> IO (Ptr CChar)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr CChar
forall a. Ptr a
FP.nullPtr
Just Text
jGroupName -> do
jGroupName' <- Text -> IO (Ptr CChar)
textToCString Text
jGroupName
return jGroupName'
onException (do
result <- propagateGError $ gtk_paper_size_new_from_key_file keyFile' maybeGroupName
checkUnexpectedReturnNULL "paperSizeNewFromKeyFile" result
result' <- (wrapBoxed PaperSize) result
touchManagedPtr keyFile
freeMem maybeGroupName
return result'
) (do
freeMem maybeGroupName
)
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_paper_size_new_from_ppd" gtk_paper_size_new_from_ppd ::
CString ->
CString ->
CDouble ->
CDouble ->
IO (Ptr PaperSize)
paperSizeNewFromPpd ::
(B.CallStack.HasCallStack, MonadIO m) =>
T.Text
-> T.Text
-> Double
-> Double
-> m PaperSize
paperSizeNewFromPpd :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Text -> Text -> Double -> Double -> m PaperSize
paperSizeNewFromPpd Text
ppdName Text
ppdDisplayName Double
width Double
height = IO PaperSize -> m PaperSize
forall a. IO a -> m a
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
ppdName' <- Text -> IO (Ptr CChar)
textToCString Text
ppdName
ppdDisplayName' <- textToCString ppdDisplayName
let width' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
width
let height' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
height
result <- gtk_paper_size_new_from_ppd ppdName' ppdDisplayName' width' height'
checkUnexpectedReturnNULL "paperSizeNewFromPpd" result
result' <- (wrapBoxed PaperSize) result
freeMem ppdName'
freeMem ppdDisplayName'
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_paper_size_copy" gtk_paper_size_copy ::
Ptr PaperSize ->
IO (Ptr PaperSize)
paperSizeCopy ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> m PaperSize
paperSizeCopy :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> m PaperSize
paperSizeCopy PaperSize
other = IO PaperSize -> m PaperSize
forall a. IO a -> m a
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
other' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
other
result <- gtk_paper_size_copy other'
checkUnexpectedReturnNULL "paperSizeCopy" result
result' <- (wrapBoxed PaperSize) result
touchManagedPtr other
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeCopyMethodInfo
instance (signature ~ (m PaperSize), MonadIO m) => O.OverloadedMethod PaperSizeCopyMethodInfo PaperSize signature where
overloadedMethod = paperSizeCopy
instance O.OverloadedMethodInfo PaperSizeCopyMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeCopy",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeCopy"
})
#endif
foreign import ccall "gtk_paper_size_free" gtk_paper_size_free ::
Ptr PaperSize ->
IO ()
paperSizeFree ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> m ()
paperSizeFree :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> m ()
paperSizeFree PaperSize
size = 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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
gtk_paper_size_free size'
touchManagedPtr size
return ()
#if defined(ENABLE_OVERLOADING)
data PaperSizeFreeMethodInfo
instance (signature ~ (m ()), MonadIO m) => O.OverloadedMethod PaperSizeFreeMethodInfo PaperSize signature where
overloadedMethod = paperSizeFree
instance O.OverloadedMethodInfo PaperSizeFreeMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeFree",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeFree"
})
#endif
foreign import ccall "gtk_paper_size_get_default_bottom_margin" gtk_paper_size_get_default_bottom_margin ::
Ptr PaperSize ->
CUInt ->
IO CDouble
paperSizeGetDefaultBottomMargin ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> Gtk.Enums.Unit
-> m Double
paperSizeGetDefaultBottomMargin :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> Unit -> m Double
paperSizeGetDefaultBottomMargin PaperSize
size Unit
unit = IO Double -> m Double
forall a. IO a -> m a
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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
let 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
result <- gtk_paper_size_get_default_bottom_margin size' unit'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeGetDefaultBottomMarginMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m) => O.OverloadedMethod PaperSizeGetDefaultBottomMarginMethodInfo PaperSize signature where
overloadedMethod = paperSizeGetDefaultBottomMargin
instance O.OverloadedMethodInfo PaperSizeGetDefaultBottomMarginMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeGetDefaultBottomMargin",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeGetDefaultBottomMargin"
})
#endif
foreign import ccall "gtk_paper_size_get_default_left_margin" gtk_paper_size_get_default_left_margin ::
Ptr PaperSize ->
CUInt ->
IO CDouble
paperSizeGetDefaultLeftMargin ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> Gtk.Enums.Unit
-> m Double
paperSizeGetDefaultLeftMargin :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> Unit -> m Double
paperSizeGetDefaultLeftMargin PaperSize
size Unit
unit = IO Double -> m Double
forall a. IO a -> m a
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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
let 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
result <- gtk_paper_size_get_default_left_margin size' unit'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeGetDefaultLeftMarginMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m) => O.OverloadedMethod PaperSizeGetDefaultLeftMarginMethodInfo PaperSize signature where
overloadedMethod = paperSizeGetDefaultLeftMargin
instance O.OverloadedMethodInfo PaperSizeGetDefaultLeftMarginMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeGetDefaultLeftMargin",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeGetDefaultLeftMargin"
})
#endif
foreign import ccall "gtk_paper_size_get_default_right_margin" gtk_paper_size_get_default_right_margin ::
Ptr PaperSize ->
CUInt ->
IO CDouble
paperSizeGetDefaultRightMargin ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> Gtk.Enums.Unit
-> m Double
paperSizeGetDefaultRightMargin :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> Unit -> m Double
paperSizeGetDefaultRightMargin PaperSize
size Unit
unit = IO Double -> m Double
forall a. IO a -> m a
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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
let 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
result <- gtk_paper_size_get_default_right_margin size' unit'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeGetDefaultRightMarginMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m) => O.OverloadedMethod PaperSizeGetDefaultRightMarginMethodInfo PaperSize signature where
overloadedMethod = paperSizeGetDefaultRightMargin
instance O.OverloadedMethodInfo PaperSizeGetDefaultRightMarginMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeGetDefaultRightMargin",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeGetDefaultRightMargin"
})
#endif
foreign import ccall "gtk_paper_size_get_default_top_margin" gtk_paper_size_get_default_top_margin ::
Ptr PaperSize ->
CUInt ->
IO CDouble
paperSizeGetDefaultTopMargin ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> Gtk.Enums.Unit
-> m Double
paperSizeGetDefaultTopMargin :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> Unit -> m Double
paperSizeGetDefaultTopMargin PaperSize
size Unit
unit = IO Double -> m Double
forall a. IO a -> m a
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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
let 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
result <- gtk_paper_size_get_default_top_margin size' unit'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeGetDefaultTopMarginMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m) => O.OverloadedMethod PaperSizeGetDefaultTopMarginMethodInfo PaperSize signature where
overloadedMethod = paperSizeGetDefaultTopMargin
instance O.OverloadedMethodInfo PaperSizeGetDefaultTopMarginMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeGetDefaultTopMargin",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeGetDefaultTopMargin"
})
#endif
foreign import ccall "gtk_paper_size_get_display_name" gtk_paper_size_get_display_name ::
Ptr PaperSize ->
IO CString
paperSizeGetDisplayName ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> m T.Text
paperSizeGetDisplayName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> m Text
paperSizeGetDisplayName PaperSize
size = 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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
result <- gtk_paper_size_get_display_name size'
checkUnexpectedReturnNULL "paperSizeGetDisplayName" result
result' <- cstringToText result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeGetDisplayNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod PaperSizeGetDisplayNameMethodInfo PaperSize signature where
overloadedMethod = paperSizeGetDisplayName
instance O.OverloadedMethodInfo PaperSizeGetDisplayNameMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeGetDisplayName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeGetDisplayName"
})
#endif
foreign import ccall "gtk_paper_size_get_height" gtk_paper_size_get_height ::
Ptr PaperSize ->
CUInt ->
IO CDouble
paperSizeGetHeight ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> Gtk.Enums.Unit
-> m Double
paperSizeGetHeight :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> Unit -> m Double
paperSizeGetHeight PaperSize
size Unit
unit = IO Double -> m Double
forall a. IO a -> m a
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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
let 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
result <- gtk_paper_size_get_height size' unit'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeGetHeightMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m) => O.OverloadedMethod PaperSizeGetHeightMethodInfo PaperSize signature where
overloadedMethod = paperSizeGetHeight
instance O.OverloadedMethodInfo PaperSizeGetHeightMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeGetHeight",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeGetHeight"
})
#endif
foreign import ccall "gtk_paper_size_get_name" gtk_paper_size_get_name ::
Ptr PaperSize ->
IO CString
paperSizeGetName ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> m T.Text
paperSizeGetName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> m Text
paperSizeGetName PaperSize
size = 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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
result <- gtk_paper_size_get_name size'
checkUnexpectedReturnNULL "paperSizeGetName" result
result' <- cstringToText result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeGetNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod PaperSizeGetNameMethodInfo PaperSize signature where
overloadedMethod = paperSizeGetName
instance O.OverloadedMethodInfo PaperSizeGetNameMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeGetName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeGetName"
})
#endif
foreign import ccall "gtk_paper_size_get_ppd_name" gtk_paper_size_get_ppd_name ::
Ptr PaperSize ->
IO CString
paperSizeGetPpdName ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> m T.Text
paperSizeGetPpdName :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> m Text
paperSizeGetPpdName PaperSize
size = 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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
result <- gtk_paper_size_get_ppd_name size'
checkUnexpectedReturnNULL "paperSizeGetPpdName" result
result' <- cstringToText result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeGetPpdNameMethodInfo
instance (signature ~ (m T.Text), MonadIO m) => O.OverloadedMethod PaperSizeGetPpdNameMethodInfo PaperSize signature where
overloadedMethod = paperSizeGetPpdName
instance O.OverloadedMethodInfo PaperSizeGetPpdNameMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeGetPpdName",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeGetPpdName"
})
#endif
foreign import ccall "gtk_paper_size_get_width" gtk_paper_size_get_width ::
Ptr PaperSize ->
CUInt ->
IO CDouble
paperSizeGetWidth ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> Gtk.Enums.Unit
-> m Double
paperSizeGetWidth :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> Unit -> m Double
paperSizeGetWidth PaperSize
size Unit
unit = IO Double -> m Double
forall a. IO a -> m a
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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
let 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
result <- gtk_paper_size_get_width size' unit'
let result' = CDouble -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac CDouble
result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeGetWidthMethodInfo
instance (signature ~ (Gtk.Enums.Unit -> m Double), MonadIO m) => O.OverloadedMethod PaperSizeGetWidthMethodInfo PaperSize signature where
overloadedMethod = paperSizeGetWidth
instance O.OverloadedMethodInfo PaperSizeGetWidthMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeGetWidth",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeGetWidth"
})
#endif
foreign import ccall "gtk_paper_size_is_custom" gtk_paper_size_is_custom ::
Ptr PaperSize ->
IO CInt
paperSizeIsCustom ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> m Bool
paperSizeIsCustom :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> m Bool
paperSizeIsCustom PaperSize
size = 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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
result <- gtk_paper_size_is_custom size'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeIsCustomMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod PaperSizeIsCustomMethodInfo PaperSize signature where
overloadedMethod = paperSizeIsCustom
instance O.OverloadedMethodInfo PaperSizeIsCustomMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeIsCustom",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeIsCustom"
})
#endif
foreign import ccall "gtk_paper_size_is_equal" gtk_paper_size_is_equal ::
Ptr PaperSize ->
Ptr PaperSize ->
IO CInt
paperSizeIsEqual ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> PaperSize
-> m Bool
paperSizeIsEqual :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> PaperSize -> m Bool
paperSizeIsEqual PaperSize
size1 PaperSize
size2 = 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
size1' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size1
size2' <- unsafeManagedPtrGetPtr size2
result <- gtk_paper_size_is_equal size1' size2'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr size1
touchManagedPtr size2
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeIsEqualMethodInfo
instance (signature ~ (PaperSize -> m Bool), MonadIO m) => O.OverloadedMethod PaperSizeIsEqualMethodInfo PaperSize signature where
overloadedMethod = paperSizeIsEqual
instance O.OverloadedMethodInfo PaperSizeIsEqualMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeIsEqual",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeIsEqual"
})
#endif
foreign import ccall "gtk_paper_size_is_ipp" gtk_paper_size_is_ipp ::
Ptr PaperSize ->
IO CInt
paperSizeIsIpp ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> m Bool
paperSizeIsIpp :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> m Bool
paperSizeIsIpp PaperSize
size = 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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
result <- gtk_paper_size_is_ipp size'
let result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
touchManagedPtr size
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeIsIppMethodInfo
instance (signature ~ (m Bool), MonadIO m) => O.OverloadedMethod PaperSizeIsIppMethodInfo PaperSize signature where
overloadedMethod = paperSizeIsIpp
instance O.OverloadedMethodInfo PaperSizeIsIppMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeIsIpp",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeIsIpp"
})
#endif
foreign import ccall "gtk_paper_size_set_size" gtk_paper_size_set_size ::
Ptr PaperSize ->
CDouble ->
CDouble ->
CUInt ->
IO ()
paperSizeSetSize ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> Double
-> Double
-> Gtk.Enums.Unit
-> m ()
paperSizeSetSize :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> Double -> Double -> Unit -> m ()
paperSizeSetSize PaperSize
size Double
width Double
height Unit
unit = 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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
let width' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
width
let height' = Double -> CDouble
forall a b. (Real a, Fractional b) => a -> b
realToFrac Double
height
let 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
gtk_paper_size_set_size size' width' height' unit'
touchManagedPtr size
return ()
#if defined(ENABLE_OVERLOADING)
data PaperSizeSetSizeMethodInfo
instance (signature ~ (Double -> Double -> Gtk.Enums.Unit -> m ()), MonadIO m) => O.OverloadedMethod PaperSizeSetSizeMethodInfo PaperSize signature where
overloadedMethod = paperSizeSetSize
instance O.OverloadedMethodInfo PaperSizeSetSizeMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeSetSize",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeSetSize"
})
#endif
foreign import ccall "gtk_paper_size_to_gvariant" gtk_paper_size_to_gvariant ::
Ptr PaperSize ->
IO (Ptr GVariant)
paperSizeToGvariant ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> m GVariant
paperSizeToGvariant :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> m GVariant
paperSizeToGvariant PaperSize
paperSize = IO GVariant -> m GVariant
forall a. IO a -> m a
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
paperSize' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
paperSize
result <- gtk_paper_size_to_gvariant paperSize'
checkUnexpectedReturnNULL "paperSizeToGvariant" result
result' <- B.GVariant.newGVariantFromPtr result
touchManagedPtr paperSize
return result'
#if defined(ENABLE_OVERLOADING)
data PaperSizeToGvariantMethodInfo
instance (signature ~ (m GVariant), MonadIO m) => O.OverloadedMethod PaperSizeToGvariantMethodInfo PaperSize signature where
overloadedMethod = paperSizeToGvariant
instance O.OverloadedMethodInfo PaperSizeToGvariantMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeToGvariant",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeToGvariant"
})
#endif
foreign import ccall "gtk_paper_size_to_key_file" gtk_paper_size_to_key_file ::
Ptr PaperSize ->
Ptr GLib.KeyFile.KeyFile ->
CString ->
IO ()
paperSizeToKeyFile ::
(B.CallStack.HasCallStack, MonadIO m) =>
PaperSize
-> GLib.KeyFile.KeyFile
-> T.Text
-> m ()
paperSizeToKeyFile :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
PaperSize -> KeyFile -> Text -> m ()
paperSizeToKeyFile PaperSize
size KeyFile
keyFile Text
groupName = 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
size' <- PaperSize -> IO (Ptr PaperSize)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr PaperSize
size
keyFile' <- unsafeManagedPtrGetPtr keyFile
groupName' <- textToCString groupName
gtk_paper_size_to_key_file size' keyFile' groupName'
touchManagedPtr size
touchManagedPtr keyFile
freeMem groupName'
return ()
#if defined(ENABLE_OVERLOADING)
data PaperSizeToKeyFileMethodInfo
instance (signature ~ (GLib.KeyFile.KeyFile -> T.Text -> m ()), MonadIO m) => O.OverloadedMethod PaperSizeToKeyFileMethodInfo PaperSize signature where
overloadedMethod = paperSizeToKeyFile
instance O.OverloadedMethodInfo PaperSizeToKeyFileMethodInfo PaperSize where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gtk.Structs.PaperSize.paperSizeToKeyFile",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gtk4-4.0.12/docs/GI-Gtk-Structs-PaperSize.html#v:paperSizeToKeyFile"
})
#endif
foreign import ccall "gtk_paper_size_get_default" gtk_paper_size_get_default ::
IO CString
paperSizeGetDefault ::
(B.CallStack.HasCallStack, MonadIO m) =>
m T.Text
paperSizeGetDefault :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m Text
paperSizeGetDefault = 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
result <- IO (Ptr CChar)
gtk_paper_size_get_default
checkUnexpectedReturnNULL "paperSizeGetDefault" result
result' <- cstringToText result
return result'
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gtk_paper_size_get_paper_sizes" gtk_paper_size_get_paper_sizes ::
CInt ->
IO (Ptr (GList (Ptr PaperSize)))
paperSizeGetPaperSizes ::
(B.CallStack.HasCallStack, MonadIO m) =>
Bool
-> m [PaperSize]
paperSizeGetPaperSizes :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
Bool -> m [PaperSize]
paperSizeGetPaperSizes Bool
includeCustom = IO [PaperSize] -> m [PaperSize]
forall a. IO a -> m a
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
let includeCustom' :: CInt
includeCustom' = (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
includeCustom
result <- CInt -> IO (Ptr (GList (Ptr PaperSize)))
gtk_paper_size_get_paper_sizes CInt
includeCustom'
result' <- unpackGList result
result'' <- mapM (wrapBoxed PaperSize) result'
g_list_free result
return result''
#if defined(ENABLE_OVERLOADING)
#endif
#if defined(ENABLE_OVERLOADING)
type family ResolvePaperSizeMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolvePaperSizeMethod "copy" o = PaperSizeCopyMethodInfo
ResolvePaperSizeMethod "free" o = PaperSizeFreeMethodInfo
ResolvePaperSizeMethod "isCustom" o = PaperSizeIsCustomMethodInfo
ResolvePaperSizeMethod "isEqual" o = PaperSizeIsEqualMethodInfo
ResolvePaperSizeMethod "isIpp" o = PaperSizeIsIppMethodInfo
ResolvePaperSizeMethod "toGvariant" o = PaperSizeToGvariantMethodInfo
ResolvePaperSizeMethod "toKeyFile" o = PaperSizeToKeyFileMethodInfo
ResolvePaperSizeMethod "getDefaultBottomMargin" o = PaperSizeGetDefaultBottomMarginMethodInfo
ResolvePaperSizeMethod "getDefaultLeftMargin" o = PaperSizeGetDefaultLeftMarginMethodInfo
ResolvePaperSizeMethod "getDefaultRightMargin" o = PaperSizeGetDefaultRightMarginMethodInfo
ResolvePaperSizeMethod "getDefaultTopMargin" o = PaperSizeGetDefaultTopMarginMethodInfo
ResolvePaperSizeMethod "getDisplayName" o = PaperSizeGetDisplayNameMethodInfo
ResolvePaperSizeMethod "getHeight" o = PaperSizeGetHeightMethodInfo
ResolvePaperSizeMethod "getName" o = PaperSizeGetNameMethodInfo
ResolvePaperSizeMethod "getPpdName" o = PaperSizeGetPpdNameMethodInfo
ResolvePaperSizeMethod "getWidth" o = PaperSizeGetWidthMethodInfo
ResolvePaperSizeMethod "setSize" o = PaperSizeSetSizeMethodInfo
ResolvePaperSizeMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolvePaperSizeMethod t PaperSize, O.OverloadedMethod info PaperSize p) => OL.IsLabel t (PaperSize -> 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 ~ ResolvePaperSizeMethod t PaperSize, O.OverloadedMethod info PaperSize p, R.HasField t PaperSize p) => R.HasField t PaperSize p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolvePaperSizeMethod t PaperSize, O.OverloadedMethodInfo info PaperSize) => OL.IsLabel t (O.MethodProxy info PaperSize) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif