{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.DrawContext
(
DrawContext(..) ,
IsDrawContext ,
toDrawContext ,
#if defined(ENABLE_OVERLOADING)
ResolveDrawContextMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DrawContextBeginFrameMethodInfo ,
#endif
drawContextBeginFrame ,
#if defined(ENABLE_OVERLOADING)
DrawContextEndFrameMethodInfo ,
#endif
drawContextEndFrame ,
#if defined(ENABLE_OVERLOADING)
DrawContextGetDisplayMethodInfo ,
#endif
drawContextGetDisplay ,
#if defined(ENABLE_OVERLOADING)
DrawContextGetFrameRegionMethodInfo ,
#endif
drawContextGetFrameRegion ,
#if defined(ENABLE_OVERLOADING)
DrawContextGetSurfaceMethodInfo ,
#endif
drawContextGetSurface ,
#if defined(ENABLE_OVERLOADING)
DrawContextIsInFrameMethodInfo ,
#endif
drawContextIsInFrame ,
#if defined(ENABLE_OVERLOADING)
DrawContextDisplayPropertyInfo ,
#endif
constructDrawContextDisplay ,
#if defined(ENABLE_OVERLOADING)
drawContextDisplay ,
#endif
getDrawContextDisplay ,
#if defined(ENABLE_OVERLOADING)
DrawContextSurfacePropertyInfo ,
#endif
constructDrawContextSurface ,
#if defined(ENABLE_OVERLOADING)
drawContextSurface ,
#endif
getDrawContextSurface ,
) 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.Cairo.Enums as Cairo.Enums
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Structs.Bytes as GLib.Bytes
import qualified GI.GLib.Structs.String as GLib.String
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Interfaces.Paintable as Gdk.Paintable
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.CairoContext as Gdk.CairoContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Clipboard as Gdk.Clipboard
import {-# SOURCE #-} qualified GI.Gdk.Objects.ContentProvider as Gdk.ContentProvider
import {-# SOURCE #-} qualified GI.Gdk.Objects.Cursor as Gdk.Cursor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Device as Gdk.Device
import {-# SOURCE #-} qualified GI.Gdk.Objects.DeviceTool as Gdk.DeviceTool
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.Event as Gdk.Event
import {-# SOURCE #-} qualified GI.Gdk.Objects.FrameClock as Gdk.FrameClock
import {-# SOURCE #-} qualified GI.Gdk.Objects.GLContext as Gdk.GLContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Monitor as Gdk.Monitor
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Snapshot as Gdk.Snapshot
import {-# SOURCE #-} qualified GI.Gdk.Objects.Surface as Gdk.Surface
import {-# SOURCE #-} qualified GI.Gdk.Objects.Texture as Gdk.Texture
import {-# SOURCE #-} qualified GI.Gdk.Objects.VulkanContext as Gdk.VulkanContext
import {-# SOURCE #-} qualified GI.Gdk.Structs.ContentFormats as Gdk.ContentFormats
import {-# SOURCE #-} qualified GI.Gdk.Structs.DmabufFormats as Gdk.DmabufFormats
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.KeymapKey as Gdk.KeymapKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.TimeCoord as Gdk.TimeCoord
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Callbacks as Gio.Callbacks
import qualified GI.Gio.Interfaces.AsyncResult as Gio.AsyncResult
import qualified GI.Gio.Interfaces.File as Gio.File
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Interfaces.Initable as Gio.Initable
import qualified GI.Gio.Interfaces.ListModel as Gio.ListModel
import qualified GI.Gio.Interfaces.LoadableIcon as Gio.LoadableIcon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext
import qualified GI.Gio.Objects.Cancellable as Gio.Cancellable
import qualified GI.Gio.Objects.InputStream as Gio.InputStream
import qualified GI.Gio.Objects.OutputStream as Gio.OutputStream
import qualified GI.Pango.Enums as Pango.Enums
#else
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.Surface as Gdk.Surface
#endif
newtype DrawContext = DrawContext (SP.ManagedPtr DrawContext)
deriving (DrawContext -> DrawContext -> Bool
(DrawContext -> DrawContext -> Bool)
-> (DrawContext -> DrawContext -> Bool) -> Eq DrawContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DrawContext -> DrawContext -> Bool
== :: DrawContext -> DrawContext -> Bool
$c/= :: DrawContext -> DrawContext -> Bool
/= :: DrawContext -> DrawContext -> Bool
Eq)
instance SP.ManagedPtrNewtype DrawContext where
toManagedPtr :: DrawContext -> ManagedPtr DrawContext
toManagedPtr (DrawContext ManagedPtr DrawContext
p) = ManagedPtr DrawContext
p
foreign import ccall "gdk_draw_context_get_type"
c_gdk_draw_context_get_type :: IO B.Types.GType
instance B.Types.TypedObject DrawContext where
glibType :: IO GType
glibType = IO GType
c_gdk_draw_context_get_type
instance B.Types.GObject DrawContext
class (SP.GObject o, O.IsDescendantOf DrawContext o) => IsDrawContext o
instance (SP.GObject o, O.IsDescendantOf DrawContext o) => IsDrawContext o
instance O.HasParentTypes DrawContext
type instance O.ParentTypes DrawContext = '[GObject.Object.Object]
toDrawContext :: (MIO.MonadIO m, IsDrawContext o) => o -> m DrawContext
toDrawContext :: forall (m :: * -> *) o.
(MonadIO m, IsDrawContext o) =>
o -> m DrawContext
toDrawContext = IO DrawContext -> m DrawContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DrawContext -> m DrawContext)
-> (o -> IO DrawContext) -> o -> m DrawContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DrawContext -> DrawContext) -> o -> IO DrawContext
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DrawContext -> DrawContext
DrawContext
instance B.GValue.IsGValue (Maybe DrawContext) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_draw_context_get_type
gvalueSet_ :: Ptr GValue -> Maybe DrawContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DrawContext
P.Nothing = Ptr GValue -> Ptr DrawContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DrawContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr DrawContext)
gvalueSet_ Ptr GValue
gv (P.Just DrawContext
obj) = DrawContext -> (Ptr DrawContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DrawContext
obj (Ptr GValue -> Ptr DrawContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DrawContext)
gvalueGet_ Ptr GValue
gv = do
Ptr DrawContext
ptr <- Ptr GValue -> IO (Ptr DrawContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DrawContext)
if Ptr DrawContext
ptr Ptr DrawContext -> Ptr DrawContext -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DrawContext
forall a. Ptr a
FP.nullPtr
then DrawContext -> Maybe DrawContext
forall a. a -> Maybe a
P.Just (DrawContext -> Maybe DrawContext)
-> IO DrawContext -> IO (Maybe DrawContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DrawContext -> DrawContext)
-> Ptr DrawContext -> IO DrawContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DrawContext -> DrawContext
DrawContext Ptr DrawContext
ptr
else Maybe DrawContext -> IO (Maybe DrawContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DrawContext
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDrawContextMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDrawContextMethod "beginFrame" o = DrawContextBeginFrameMethodInfo
ResolveDrawContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDrawContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDrawContextMethod "endFrame" o = DrawContextEndFrameMethodInfo
ResolveDrawContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDrawContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDrawContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDrawContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDrawContextMethod "isInFrame" o = DrawContextIsInFrameMethodInfo
ResolveDrawContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDrawContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDrawContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDrawContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDrawContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDrawContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDrawContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDrawContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDrawContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDrawContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDrawContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDrawContextMethod "getDisplay" o = DrawContextGetDisplayMethodInfo
ResolveDrawContextMethod "getFrameRegion" o = DrawContextGetFrameRegionMethodInfo
ResolveDrawContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDrawContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDrawContextMethod "getSurface" o = DrawContextGetSurfaceMethodInfo
ResolveDrawContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDrawContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDrawContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDrawContextMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDrawContextMethod t DrawContext, O.OverloadedMethod info DrawContext p) => OL.IsLabel t (DrawContext -> 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 ~ ResolveDrawContextMethod t DrawContext, O.OverloadedMethod info DrawContext p, R.HasField t DrawContext p) => R.HasField t DrawContext p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDrawContextMethod t DrawContext, O.OverloadedMethodInfo info DrawContext) => OL.IsLabel t (O.MethodProxy info DrawContext) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getDrawContextDisplay :: (MonadIO m, IsDrawContext o) => o -> m (Maybe Gdk.Display.Display)
getDrawContextDisplay :: forall (m :: * -> *) o.
(MonadIO m, IsDrawContext o) =>
o -> m (Maybe Display)
getDrawContextDisplay o
obj = IO (Maybe Display) -> m (Maybe Display)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Display -> Display) -> IO (Maybe Display)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"display" ManagedPtr Display -> Display
Gdk.Display.Display
constructDrawContextDisplay :: (IsDrawContext o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructDrawContextDisplay :: forall o (m :: * -> *) a.
(IsDrawContext o, MonadIO m, IsDisplay a) =>
a -> m (GValueConstruct o)
constructDrawContextDisplay a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"display" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data DrawContextDisplayPropertyInfo
instance AttrInfo DrawContextDisplayPropertyInfo where
type AttrAllowedOps DrawContextDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DrawContextDisplayPropertyInfo = IsDrawContext
type AttrSetTypeConstraint DrawContextDisplayPropertyInfo = Gdk.Display.IsDisplay
type AttrTransferTypeConstraint DrawContextDisplayPropertyInfo = Gdk.Display.IsDisplay
type AttrTransferType DrawContextDisplayPropertyInfo = Gdk.Display.Display
type AttrGetType DrawContextDisplayPropertyInfo = (Maybe Gdk.Display.Display)
type AttrLabel DrawContextDisplayPropertyInfo = "display"
type AttrOrigin DrawContextDisplayPropertyInfo = DrawContext
attrGet = getDrawContextDisplay
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gdk.Display.Display v
attrConstruct = constructDrawContextDisplay
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawContext.display"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.8/docs/GI-Gdk-Objects-DrawContext.html#g:attr:display"
})
#endif
getDrawContextSurface :: (MonadIO m, IsDrawContext o) => o -> m (Maybe Gdk.Surface.Surface)
getDrawContextSurface :: forall (m :: * -> *) o.
(MonadIO m, IsDrawContext o) =>
o -> m (Maybe Surface)
getDrawContextSurface o
obj = IO (Maybe Surface) -> m (Maybe Surface)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Surface) -> m (Maybe Surface))
-> IO (Maybe Surface) -> m (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Surface -> Surface) -> IO (Maybe Surface)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"surface" ManagedPtr Surface -> Surface
Gdk.Surface.Surface
constructDrawContextSurface :: (IsDrawContext o, MIO.MonadIO m, Gdk.Surface.IsSurface a) => a -> m (GValueConstruct o)
constructDrawContextSurface :: forall o (m :: * -> *) a.
(IsDrawContext o, MonadIO m, IsSurface a) =>
a -> m (GValueConstruct o)
constructDrawContextSurface a
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 a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"surface" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data DrawContextSurfacePropertyInfo
instance AttrInfo DrawContextSurfacePropertyInfo where
type AttrAllowedOps DrawContextSurfacePropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DrawContextSurfacePropertyInfo = IsDrawContext
type AttrSetTypeConstraint DrawContextSurfacePropertyInfo = Gdk.Surface.IsSurface
type AttrTransferTypeConstraint DrawContextSurfacePropertyInfo = Gdk.Surface.IsSurface
type AttrTransferType DrawContextSurfacePropertyInfo = Gdk.Surface.Surface
type AttrGetType DrawContextSurfacePropertyInfo = (Maybe Gdk.Surface.Surface)
type AttrLabel DrawContextSurfacePropertyInfo = "surface"
type AttrOrigin DrawContextSurfacePropertyInfo = DrawContext
attrGet = getDrawContextSurface
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gdk.Surface.Surface v
attrConstruct = constructDrawContextSurface
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawContext.surface"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.8/docs/GI-Gdk-Objects-DrawContext.html#g:attr:surface"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DrawContext
type instance O.AttributeList DrawContext = DrawContextAttributeList
type DrawContextAttributeList = ('[ '("display", DrawContextDisplayPropertyInfo), '("surface", DrawContextSurfacePropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
drawContextDisplay :: AttrLabelProxy "display"
drawContextDisplay = AttrLabelProxy
drawContextSurface :: AttrLabelProxy "surface"
drawContextSurface = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DrawContext = DrawContextSignalList
type DrawContextSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gdk_draw_context_begin_frame" gdk_draw_context_begin_frame ::
Ptr DrawContext ->
Ptr Cairo.Region.Region ->
IO ()
drawContextBeginFrame ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
a
-> Cairo.Region.Region
-> m ()
drawContextBeginFrame :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> Region -> m ()
drawContextBeginFrame a
context Region
region = 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
Ptr DrawContext
context' <- a -> IO (Ptr DrawContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr Region
region' <- Region -> IO (Ptr Region)
forall a. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr a)
unsafeManagedPtrGetPtr Region
region
Ptr DrawContext -> Ptr Region -> IO ()
gdk_draw_context_begin_frame Ptr DrawContext
context' Ptr Region
region'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Region -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr Region
region
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DrawContextBeginFrameMethodInfo
instance (signature ~ (Cairo.Region.Region -> m ()), MonadIO m, IsDrawContext a) => O.OverloadedMethod DrawContextBeginFrameMethodInfo a signature where
overloadedMethod = drawContextBeginFrame
instance O.OverloadedMethodInfo DrawContextBeginFrameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawContext.drawContextBeginFrame",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.8/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextBeginFrame"
})
#endif
foreign import ccall "gdk_draw_context_end_frame" gdk_draw_context_end_frame ::
Ptr DrawContext ->
IO ()
drawContextEndFrame ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
a
-> m ()
drawContextEndFrame :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m ()
drawContextEndFrame a
context = 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
Ptr DrawContext
context' <- a -> IO (Ptr DrawContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr DrawContext -> IO ()
gdk_draw_context_end_frame Ptr DrawContext
context'
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data DrawContextEndFrameMethodInfo
instance (signature ~ (m ()), MonadIO m, IsDrawContext a) => O.OverloadedMethod DrawContextEndFrameMethodInfo a signature where
overloadedMethod = drawContextEndFrame
instance O.OverloadedMethodInfo DrawContextEndFrameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawContext.drawContextEndFrame",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.8/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextEndFrame"
})
#endif
foreign import ccall "gdk_draw_context_get_display" gdk_draw_context_get_display ::
Ptr DrawContext ->
IO (Ptr Gdk.Display.Display)
drawContextGetDisplay ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
a
-> m (Maybe Gdk.Display.Display)
drawContextGetDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m (Maybe Display)
drawContextGetDisplay a
context = IO (Maybe Display) -> m (Maybe Display)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ do
Ptr DrawContext
context' <- a -> IO (Ptr DrawContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr Display
result <- Ptr DrawContext -> IO (Ptr Display)
gdk_draw_context_get_display Ptr DrawContext
context'
Maybe Display
maybeResult <- Ptr Display -> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Display
result ((Ptr Display -> IO Display) -> IO (Maybe Display))
-> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. (a -> b) -> a -> b
$ \Ptr Display
result' -> do
Display
result'' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
result'
Display -> IO Display
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Maybe Display -> IO (Maybe Display)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult
#if defined(ENABLE_OVERLOADING)
data DrawContextGetDisplayMethodInfo
instance (signature ~ (m (Maybe Gdk.Display.Display)), MonadIO m, IsDrawContext a) => O.OverloadedMethod DrawContextGetDisplayMethodInfo a signature where
overloadedMethod = drawContextGetDisplay
instance O.OverloadedMethodInfo DrawContextGetDisplayMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawContext.drawContextGetDisplay",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.8/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextGetDisplay"
})
#endif
foreign import ccall "gdk_draw_context_get_frame_region" gdk_draw_context_get_frame_region ::
Ptr DrawContext ->
IO (Ptr Cairo.Region.Region)
drawContextGetFrameRegion ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
a
-> m (Maybe Cairo.Region.Region)
drawContextGetFrameRegion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m (Maybe Region)
drawContextGetFrameRegion a
context = IO (Maybe Region) -> m (Maybe Region)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Region) -> m (Maybe Region))
-> IO (Maybe Region) -> m (Maybe Region)
forall a b. (a -> b) -> a -> b
$ do
Ptr DrawContext
context' <- a -> IO (Ptr DrawContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr Region
result <- Ptr DrawContext -> IO (Ptr Region)
gdk_draw_context_get_frame_region Ptr DrawContext
context'
Maybe Region
maybeResult <- Ptr Region -> (Ptr Region -> IO Region) -> IO (Maybe Region)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Region
result ((Ptr Region -> IO Region) -> IO (Maybe Region))
-> (Ptr Region -> IO Region) -> IO (Maybe Region)
forall a b. (a -> b) -> a -> b
$ \Ptr Region
result' -> do
Region
result'' <- ((ManagedPtr Region -> Region) -> Ptr Region -> IO Region
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Region -> Region
Cairo.Region.Region) Ptr Region
result'
Region -> IO Region
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Region
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Maybe Region -> IO (Maybe Region)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Region
maybeResult
#if defined(ENABLE_OVERLOADING)
data DrawContextGetFrameRegionMethodInfo
instance (signature ~ (m (Maybe Cairo.Region.Region)), MonadIO m, IsDrawContext a) => O.OverloadedMethod DrawContextGetFrameRegionMethodInfo a signature where
overloadedMethod = drawContextGetFrameRegion
instance O.OverloadedMethodInfo DrawContextGetFrameRegionMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawContext.drawContextGetFrameRegion",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.8/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextGetFrameRegion"
})
#endif
foreign import ccall "gdk_draw_context_get_surface" gdk_draw_context_get_surface ::
Ptr DrawContext ->
IO (Ptr Gdk.Surface.Surface)
drawContextGetSurface ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
a
-> m (Maybe Gdk.Surface.Surface)
drawContextGetSurface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m (Maybe Surface)
drawContextGetSurface a
context = IO (Maybe Surface) -> m (Maybe Surface)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Surface) -> m (Maybe Surface))
-> IO (Maybe Surface) -> m (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ do
Ptr DrawContext
context' <- a -> IO (Ptr DrawContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr Surface
result <- Ptr DrawContext -> IO (Ptr Surface)
gdk_draw_context_get_surface Ptr DrawContext
context'
Maybe Surface
maybeResult <- Ptr Surface -> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Surface
result ((Ptr Surface -> IO Surface) -> IO (Maybe Surface))
-> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ \Ptr Surface
result' -> do
Surface
result'' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Surface -> Surface
Gdk.Surface.Surface) Ptr Surface
result'
Surface -> IO Surface
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result''
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Maybe Surface -> IO (Maybe Surface)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Surface
maybeResult
#if defined(ENABLE_OVERLOADING)
data DrawContextGetSurfaceMethodInfo
instance (signature ~ (m (Maybe Gdk.Surface.Surface)), MonadIO m, IsDrawContext a) => O.OverloadedMethod DrawContextGetSurfaceMethodInfo a signature where
overloadedMethod = drawContextGetSurface
instance O.OverloadedMethodInfo DrawContextGetSurfaceMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawContext.drawContextGetSurface",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.8/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextGetSurface"
})
#endif
foreign import ccall "gdk_draw_context_is_in_frame" gdk_draw_context_is_in_frame ::
Ptr DrawContext ->
IO CInt
drawContextIsInFrame ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
a
-> m Bool
drawContextIsInFrame :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m Bool
drawContextIsInFrame a
context = 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
Ptr DrawContext
context' <- a -> IO (Ptr DrawContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
CInt
result <- Ptr DrawContext -> IO CInt
gdk_draw_context_is_in_frame Ptr DrawContext
context'
let result' :: Bool
result' = (CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data DrawContextIsInFrameMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrawContext a) => O.OverloadedMethod DrawContextIsInFrameMethodInfo a signature where
overloadedMethod = drawContextIsInFrame
instance O.OverloadedMethodInfo DrawContextIsInFrameMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawContext.drawContextIsInFrame",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.8/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextIsInFrame"
})
#endif