{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.DrawingContext
(
DrawingContext(..) ,
IsDrawingContext ,
toDrawingContext ,
#if defined(ENABLE_OVERLOADING)
ResolveDrawingContextMethod ,
#endif
#if defined(ENABLE_OVERLOADING)
DrawingContextGetCairoContextMethodInfo ,
#endif
drawingContextGetCairoContext ,
#if defined(ENABLE_OVERLOADING)
DrawingContextGetClipMethodInfo ,
#endif
drawingContextGetClip ,
#if defined(ENABLE_OVERLOADING)
DrawingContextGetWindowMethodInfo ,
#endif
drawingContextGetWindow ,
#if defined(ENABLE_OVERLOADING)
DrawingContextIsValidMethodInfo ,
#endif
drawingContextIsValid ,
#if defined(ENABLE_OVERLOADING)
DrawingContextClipPropertyInfo ,
#endif
constructDrawingContextClip ,
#if defined(ENABLE_OVERLOADING)
drawingContextClip ,
#endif
getDrawingContextClip ,
#if defined(ENABLE_OVERLOADING)
DrawingContextWindowPropertyInfo ,
#endif
constructDrawingContextWindow ,
#if defined(ENABLE_OVERLOADING)
drawingContextWindow ,
#endif
getDrawingContextWindow ,
) 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.FontOptions as Cairo.FontOptions
import qualified GI.Cairo.Structs.Pattern as Cairo.Pattern
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.Cairo.Structs.Surface as Cairo.Surface
import qualified GI.GLib.Callbacks as GLib.Callbacks
import qualified GI.GObject.Objects.Object as GObject.Object
import qualified GI.Gdk.Callbacks as Gdk.Callbacks
import {-# SOURCE #-} qualified GI.Gdk.Enums as Gdk.Enums
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.AppLaunchContext as Gdk.AppLaunchContext
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.DeviceManager as Gdk.DeviceManager
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.DragContext as Gdk.DragContext
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.Screen as Gdk.Screen
import {-# SOURCE #-} qualified GI.Gdk.Objects.Seat as Gdk.Seat
import {-# SOURCE #-} qualified GI.Gdk.Objects.Visual as Gdk.Visual
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
import {-# SOURCE #-} qualified GI.Gdk.Structs.Atom as Gdk.Atom
import {-# SOURCE #-} qualified GI.Gdk.Structs.Color as Gdk.Color
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventAny as Gdk.EventAny
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventButton as Gdk.EventButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventConfigure as Gdk.EventConfigure
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventCrossing as Gdk.EventCrossing
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventDND as Gdk.EventDND
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventExpose as Gdk.EventExpose
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventFocus as Gdk.EventFocus
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventGrabBroken as Gdk.EventGrabBroken
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventKey as Gdk.EventKey
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventMotion as Gdk.EventMotion
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventOwnerChange as Gdk.EventOwnerChange
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadAxis as Gdk.EventPadAxis
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadButton as Gdk.EventPadButton
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventPadGroupMode as Gdk.EventPadGroupMode
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProperty as Gdk.EventProperty
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventProximity as Gdk.EventProximity
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventScroll as Gdk.EventScroll
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSelection as Gdk.EventSelection
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSequence as Gdk.EventSequence
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventSetting as Gdk.EventSetting
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouch as Gdk.EventTouch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadPinch as Gdk.EventTouchpadPinch
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventTouchpadSwipe as Gdk.EventTouchpadSwipe
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventVisibility as Gdk.EventVisibility
import {-# SOURCE #-} qualified GI.Gdk.Structs.EventWindowState as Gdk.EventWindowState
import {-# SOURCE #-} qualified GI.Gdk.Structs.FrameTimings as Gdk.FrameTimings
import {-# SOURCE #-} qualified GI.Gdk.Structs.Geometry as Gdk.Geometry
import {-# SOURCE #-} qualified GI.Gdk.Structs.RGBA as Gdk.RGBA
import {-# SOURCE #-} qualified GI.Gdk.Structs.Rectangle as Gdk.Rectangle
import {-# SOURCE #-} qualified GI.Gdk.Structs.WindowAttr as Gdk.WindowAttr
import {-# SOURCE #-} qualified GI.Gdk.Unions.Event as Gdk.Event
import qualified GI.GdkPixbuf.Objects.Pixbuf as GdkPixbuf.Pixbuf
import qualified GI.Gio.Interfaces.Icon as Gio.Icon
import qualified GI.Gio.Objects.AppLaunchContext as Gio.AppLaunchContext
#else
import qualified GI.Cairo.Structs.Context as Cairo.Context
import qualified GI.Cairo.Structs.Region as Cairo.Region
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
#endif
newtype DrawingContext = DrawingContext (SP.ManagedPtr DrawingContext)
deriving (DrawingContext -> DrawingContext -> Bool
(DrawingContext -> DrawingContext -> Bool)
-> (DrawingContext -> DrawingContext -> Bool) -> Eq DrawingContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DrawingContext -> DrawingContext -> Bool
== :: DrawingContext -> DrawingContext -> Bool
$c/= :: DrawingContext -> DrawingContext -> Bool
/= :: DrawingContext -> DrawingContext -> Bool
Eq)
instance SP.ManagedPtrNewtype DrawingContext where
toManagedPtr :: DrawingContext -> ManagedPtr DrawingContext
toManagedPtr (DrawingContext ManagedPtr DrawingContext
p) = ManagedPtr DrawingContext
p
foreign import ccall "gdk_drawing_context_get_type"
c_gdk_drawing_context_get_type :: IO B.Types.GType
instance B.Types.TypedObject DrawingContext where
glibType :: IO GType
glibType = IO GType
c_gdk_drawing_context_get_type
instance B.Types.GObject DrawingContext
class (SP.GObject o, O.IsDescendantOf DrawingContext o) => IsDrawingContext o
instance (SP.GObject o, O.IsDescendantOf DrawingContext o) => IsDrawingContext o
instance O.HasParentTypes DrawingContext
type instance O.ParentTypes DrawingContext = '[GObject.Object.Object]
toDrawingContext :: (MIO.MonadIO m, IsDrawingContext o) => o -> m DrawingContext
toDrawingContext :: forall (m :: * -> *) o.
(MonadIO m, IsDrawingContext o) =>
o -> m DrawingContext
toDrawingContext = IO DrawingContext -> m DrawingContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO DrawingContext -> m DrawingContext)
-> (o -> IO DrawingContext) -> o -> m DrawingContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr DrawingContext -> DrawingContext)
-> o -> IO DrawingContext
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr DrawingContext -> DrawingContext
DrawingContext
instance B.GValue.IsGValue (Maybe DrawingContext) where
gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_drawing_context_get_type
gvalueSet_ :: Ptr GValue -> Maybe DrawingContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe DrawingContext
P.Nothing = Ptr GValue -> Ptr DrawingContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr DrawingContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr DrawingContext)
gvalueSet_ Ptr GValue
gv (P.Just DrawingContext
obj) = DrawingContext -> (Ptr DrawingContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DrawingContext
obj (Ptr GValue -> Ptr DrawingContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
gvalueGet_ :: Ptr GValue -> IO (Maybe DrawingContext)
gvalueGet_ Ptr GValue
gv = do
Ptr DrawingContext
ptr <- Ptr GValue -> IO (Ptr DrawingContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr DrawingContext)
if Ptr DrawingContext
ptr Ptr DrawingContext -> Ptr DrawingContext -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr DrawingContext
forall a. Ptr a
FP.nullPtr
then DrawingContext -> Maybe DrawingContext
forall a. a -> Maybe a
P.Just (DrawingContext -> Maybe DrawingContext)
-> IO DrawingContext -> IO (Maybe DrawingContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr DrawingContext -> DrawingContext)
-> Ptr DrawingContext -> IO DrawingContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr DrawingContext -> DrawingContext
DrawingContext Ptr DrawingContext
ptr
else Maybe DrawingContext -> IO (Maybe DrawingContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe DrawingContext
forall a. Maybe a
P.Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDrawingContextMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
ResolveDrawingContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
ResolveDrawingContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
ResolveDrawingContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
ResolveDrawingContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
ResolveDrawingContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
ResolveDrawingContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
ResolveDrawingContextMethod "isValid" o = DrawingContextIsValidMethodInfo
ResolveDrawingContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
ResolveDrawingContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
ResolveDrawingContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
ResolveDrawingContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
ResolveDrawingContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
ResolveDrawingContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
ResolveDrawingContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
ResolveDrawingContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
ResolveDrawingContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
ResolveDrawingContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
ResolveDrawingContextMethod "getCairoContext" o = DrawingContextGetCairoContextMethodInfo
ResolveDrawingContextMethod "getClip" o = DrawingContextGetClipMethodInfo
ResolveDrawingContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
ResolveDrawingContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
ResolveDrawingContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
ResolveDrawingContextMethod "getWindow" o = DrawingContextGetWindowMethodInfo
ResolveDrawingContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
ResolveDrawingContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
ResolveDrawingContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
ResolveDrawingContextMethod l o = O.MethodResolutionFailed l o
instance (info ~ ResolveDrawingContextMethod t DrawingContext, O.OverloadedMethod info DrawingContext p) => OL.IsLabel t (DrawingContext -> 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 ~ ResolveDrawingContextMethod t DrawingContext, O.OverloadedMethod info DrawingContext p, R.HasField t DrawingContext p) => R.HasField t DrawingContext p where
getField = O.overloadedMethod @info
#endif
instance (info ~ ResolveDrawingContextMethod t DrawingContext, O.OverloadedMethodInfo info DrawingContext) => OL.IsLabel t (O.MethodProxy info DrawingContext) where
#if MIN_VERSION_base(4,10,0)
fromLabel = O.MethodProxy
#else
fromLabel _ = O.MethodProxy
#endif
#endif
getDrawingContextClip :: (MonadIO m, IsDrawingContext o) => o -> m (Maybe Cairo.Region.Region)
getDrawingContextClip :: forall (m :: * -> *) o.
(MonadIO m, IsDrawingContext o) =>
o -> m (Maybe Region)
getDrawingContextClip o
obj = IO (Maybe Region) -> m (Maybe Region)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Region) -> m (Maybe Region))
-> IO (Maybe Region) -> m (Maybe Region)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Region -> Region) -> IO (Maybe Region)
forall a b.
(GObject a, GBoxed b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj String
"clip" ManagedPtr Region -> Region
Cairo.Region.Region
constructDrawingContextClip :: (IsDrawingContext o, MIO.MonadIO m) => Cairo.Region.Region -> m (GValueConstruct o)
constructDrawingContextClip :: forall o (m :: * -> *).
(IsDrawingContext o, MonadIO m) =>
Region -> m (GValueConstruct o)
constructDrawingContextClip Region
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 Region -> IO (GValueConstruct o)
forall a o. GBoxed a => String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed String
"clip" (Region -> Maybe Region
forall a. a -> Maybe a
P.Just Region
val)
#if defined(ENABLE_OVERLOADING)
data DrawingContextClipPropertyInfo
instance AttrInfo DrawingContextClipPropertyInfo where
type AttrAllowedOps DrawingContextClipPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DrawingContextClipPropertyInfo = IsDrawingContext
type AttrSetTypeConstraint DrawingContextClipPropertyInfo = (~) Cairo.Region.Region
type AttrTransferTypeConstraint DrawingContextClipPropertyInfo = (~) Cairo.Region.Region
type AttrTransferType DrawingContextClipPropertyInfo = Cairo.Region.Region
type AttrGetType DrawingContextClipPropertyInfo = (Maybe Cairo.Region.Region)
type AttrLabel DrawingContextClipPropertyInfo = "clip"
type AttrOrigin DrawingContextClipPropertyInfo = DrawingContext
attrGet = getDrawingContextClip
attrSet = undefined
attrTransfer _ v = do
return v
attrConstruct = constructDrawingContextClip
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawingContext.clip"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DrawingContext.html#g:attr:clip"
})
#endif
getDrawingContextWindow :: (MonadIO m, IsDrawingContext o) => o -> m Gdk.Window.Window
getDrawingContextWindow :: forall (m :: * -> *) o.
(MonadIO m, IsDrawingContext o) =>
o -> m Window
getDrawingContextWindow o
obj = IO Window -> m Window
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ Text -> IO (Maybe Window) -> IO Window
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing Text
"getDrawingContextWindow" (IO (Maybe Window) -> IO Window) -> IO (Maybe Window) -> IO Window
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Window -> Window) -> IO (Maybe Window)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"window" ManagedPtr Window -> Window
Gdk.Window.Window
constructDrawingContextWindow :: (IsDrawingContext o, MIO.MonadIO m, Gdk.Window.IsWindow a) => a -> m (GValueConstruct o)
constructDrawingContextWindow :: forall o (m :: * -> *) a.
(IsDrawingContext o, MonadIO m, IsWindow a) =>
a -> m (GValueConstruct o)
constructDrawingContextWindow 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
"window" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data DrawingContextWindowPropertyInfo
instance AttrInfo DrawingContextWindowPropertyInfo where
type AttrAllowedOps DrawingContextWindowPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
type AttrBaseTypeConstraint DrawingContextWindowPropertyInfo = IsDrawingContext
type AttrSetTypeConstraint DrawingContextWindowPropertyInfo = Gdk.Window.IsWindow
type AttrTransferTypeConstraint DrawingContextWindowPropertyInfo = Gdk.Window.IsWindow
type AttrTransferType DrawingContextWindowPropertyInfo = Gdk.Window.Window
type AttrGetType DrawingContextWindowPropertyInfo = Gdk.Window.Window
type AttrLabel DrawingContextWindowPropertyInfo = "window"
type AttrOrigin DrawingContextWindowPropertyInfo = DrawingContext
attrGet = getDrawingContextWindow
attrSet = undefined
attrTransfer _ v = do
unsafeCastTo Gdk.Window.Window v
attrConstruct = constructDrawingContextWindow
attrClear = undefined
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawingContext.window"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DrawingContext.html#g:attr:window"
})
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DrawingContext
type instance O.AttributeList DrawingContext = DrawingContextAttributeList
type DrawingContextAttributeList = ('[ '("clip", DrawingContextClipPropertyInfo), '("window", DrawingContextWindowPropertyInfo)] :: [(Symbol, DK.Type)])
#endif
#if defined(ENABLE_OVERLOADING)
drawingContextClip :: AttrLabelProxy "clip"
drawingContextClip = AttrLabelProxy
drawingContextWindow :: AttrLabelProxy "window"
drawingContextWindow = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList DrawingContext = DrawingContextSignalList
type DrawingContextSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])
#endif
foreign import ccall "gdk_drawing_context_get_cairo_context" gdk_drawing_context_get_cairo_context ::
Ptr DrawingContext ->
IO (Ptr Cairo.Context.Context)
drawingContextGetCairoContext ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawingContext a) =>
a
-> m Cairo.Context.Context
drawingContextGetCairoContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawingContext a) =>
a -> m Context
drawingContextGetCairoContext a
context = IO Context -> m Context
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Context -> m Context) -> IO Context -> m Context
forall a b. (a -> b) -> a -> b
$ do
Ptr DrawingContext
context' <- a -> IO (Ptr DrawingContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr Context
result <- Ptr DrawingContext -> IO (Ptr Context)
gdk_drawing_context_get_cairo_context Ptr DrawingContext
context'
Text -> Ptr Context -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"drawingContextGetCairoContext" Ptr Context
result
Context
result' <- ((ManagedPtr Context -> Context) -> Ptr Context -> IO Context
forall a.
(HasCallStack, GBoxed a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
newBoxed ManagedPtr Context -> Context
Cairo.Context.Context) Ptr Context
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Context -> IO Context
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Context
result'
#if defined(ENABLE_OVERLOADING)
data DrawingContextGetCairoContextMethodInfo
instance (signature ~ (m Cairo.Context.Context), MonadIO m, IsDrawingContext a) => O.OverloadedMethod DrawingContextGetCairoContextMethodInfo a signature where
overloadedMethod = drawingContextGetCairoContext
instance O.OverloadedMethodInfo DrawingContextGetCairoContextMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawingContext.drawingContextGetCairoContext",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DrawingContext.html#v:drawingContextGetCairoContext"
})
#endif
foreign import ccall "gdk_drawing_context_get_clip" gdk_drawing_context_get_clip ::
Ptr DrawingContext ->
IO (Ptr Cairo.Region.Region)
drawingContextGetClip ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawingContext a) =>
a
-> m (Maybe Cairo.Region.Region)
drawingContextGetClip :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawingContext a) =>
a -> m (Maybe Region)
drawingContextGetClip 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 DrawingContext
context' <- a -> IO (Ptr DrawingContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr Region
result <- Ptr DrawingContext -> IO (Ptr Region)
gdk_drawing_context_get_clip Ptr DrawingContext
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
wrapBoxed 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 DrawingContextGetClipMethodInfo
instance (signature ~ (m (Maybe Cairo.Region.Region)), MonadIO m, IsDrawingContext a) => O.OverloadedMethod DrawingContextGetClipMethodInfo a signature where
overloadedMethod = drawingContextGetClip
instance O.OverloadedMethodInfo DrawingContextGetClipMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawingContext.drawingContextGetClip",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DrawingContext.html#v:drawingContextGetClip"
})
#endif
foreign import ccall "gdk_drawing_context_get_window" gdk_drawing_context_get_window ::
Ptr DrawingContext ->
IO (Ptr Gdk.Window.Window)
drawingContextGetWindow ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawingContext a) =>
a
-> m Gdk.Window.Window
drawingContextGetWindow :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawingContext a) =>
a -> m Window
drawingContextGetWindow a
context = IO Window -> m Window
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Window -> m Window) -> IO Window -> m Window
forall a b. (a -> b) -> a -> b
$ do
Ptr DrawingContext
context' <- a -> IO (Ptr DrawingContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
Ptr Window
result <- Ptr DrawingContext -> IO (Ptr Window)
gdk_drawing_context_get_window Ptr DrawingContext
context'
Text -> Ptr Window -> IO ()
forall a. HasCallStack => Text -> Ptr a -> IO ()
checkUnexpectedReturnNULL Text
"drawingContextGetWindow" Ptr Window
result
Window
result' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Window -> IO Window
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result'
#if defined(ENABLE_OVERLOADING)
data DrawingContextGetWindowMethodInfo
instance (signature ~ (m Gdk.Window.Window), MonadIO m, IsDrawingContext a) => O.OverloadedMethod DrawingContextGetWindowMethodInfo a signature where
overloadedMethod = drawingContextGetWindow
instance O.OverloadedMethodInfo DrawingContextGetWindowMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawingContext.drawingContextGetWindow",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DrawingContext.html#v:drawingContextGetWindow"
})
#endif
foreign import ccall "gdk_drawing_context_is_valid" gdk_drawing_context_is_valid ::
Ptr DrawingContext ->
IO CInt
drawingContextIsValid ::
(B.CallStack.HasCallStack, MonadIO m, IsDrawingContext a) =>
a
-> m Bool
drawingContextIsValid :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawingContext a) =>
a -> m Bool
drawingContextIsValid 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 DrawingContext
context' <- a -> IO (Ptr DrawingContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
CInt
result <- Ptr DrawingContext -> IO CInt
gdk_drawing_context_is_valid Ptr DrawingContext
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 DrawingContextIsValidMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrawingContext a) => O.OverloadedMethod DrawingContextIsValidMethodInfo a signature where
overloadedMethod = drawingContextIsValid
instance O.OverloadedMethodInfo DrawingContextIsValidMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.DrawingContext.drawingContextIsValid",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.29/docs/GI-Gdk-Objects-DrawingContext.html#v:drawingContextIsValid"
})
#endif