{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- Base class for objects implementing different rendering methods.
-- 
-- @GdkDrawContext@ is the base object used by contexts implementing different
-- rendering methods, such as t'GI.Gdk.Objects.CairoContext.CairoContext' or t'GI.Gdk.Objects.GLContext.GLContext'.
-- It provides shared functionality between those contexts.
-- 
-- You will always interact with one of those subclasses.
-- 
-- A @GdkDrawContext@ is always associated with a single toplevel surface.

#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif

module GI.Gdk.Objects.DrawContext
    ( 

-- * Exported types
    DrawContext(..)                         ,
    IsDrawContext                           ,
    toDrawContext                           ,


 -- * Methods
-- | 
-- 
--  === __Click to display all available methods, including inherited ones__
-- ==== Methods
-- [beginFrame]("GI.Gdk.Objects.DrawContext#g:method:beginFrame"), [bindProperty]("GI.GObject.Objects.Object#g:method:bindProperty"), [bindPropertyFull]("GI.GObject.Objects.Object#g:method:bindPropertyFull"), [endFrame]("GI.Gdk.Objects.DrawContext#g:method:endFrame"), [forceFloating]("GI.GObject.Objects.Object#g:method:forceFloating"), [freezeNotify]("GI.GObject.Objects.Object#g:method:freezeNotify"), [getv]("GI.GObject.Objects.Object#g:method:getv"), [isFloating]("GI.GObject.Objects.Object#g:method:isFloating"), [isInFrame]("GI.Gdk.Objects.DrawContext#g:method:isInFrame"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [ref]("GI.GObject.Objects.Object#g:method:ref"), [refSink]("GI.GObject.Objects.Object#g:method:refSink"), [runDispose]("GI.GObject.Objects.Object#g:method:runDispose"), [stealData]("GI.GObject.Objects.Object#g:method:stealData"), [stealQdata]("GI.GObject.Objects.Object#g:method:stealQdata"), [thawNotify]("GI.GObject.Objects.Object#g:method:thawNotify"), [unref]("GI.GObject.Objects.Object#g:method:unref"), [watchClosure]("GI.GObject.Objects.Object#g:method:watchClosure").
-- 
-- ==== Getters
-- [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDisplay]("GI.Gdk.Objects.DrawContext#g:method:getDisplay"), [getFrameRegion]("GI.Gdk.Objects.DrawContext#g:method:getFrameRegion"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getSurface]("GI.Gdk.Objects.DrawContext#g:method:getSurface").
-- 
-- ==== Setters
-- [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty").

#if defined(ENABLE_OVERLOADING)
    ResolveDrawContextMethod                ,
#endif

-- ** beginFrame #method:beginFrame#

#if defined(ENABLE_OVERLOADING)
    DrawContextBeginFrameMethodInfo         ,
#endif
    drawContextBeginFrame                   ,


-- ** endFrame #method:endFrame#

#if defined(ENABLE_OVERLOADING)
    DrawContextEndFrameMethodInfo           ,
#endif
    drawContextEndFrame                     ,


-- ** getDisplay #method:getDisplay#

#if defined(ENABLE_OVERLOADING)
    DrawContextGetDisplayMethodInfo         ,
#endif
    drawContextGetDisplay                   ,


-- ** getFrameRegion #method:getFrameRegion#

#if defined(ENABLE_OVERLOADING)
    DrawContextGetFrameRegionMethodInfo     ,
#endif
    drawContextGetFrameRegion               ,


-- ** getSurface #method:getSurface#

#if defined(ENABLE_OVERLOADING)
    DrawContextGetSurfaceMethodInfo         ,
#endif
    drawContextGetSurface                   ,


-- ** isInFrame #method:isInFrame#

#if defined(ENABLE_OVERLOADING)
    DrawContextIsInFrameMethodInfo          ,
#endif
    drawContextIsInFrame                    ,




 -- * Properties


-- ** display #attr:display#
-- | The @GdkDisplay@ used to create the @GdkDrawContext@.

#if defined(ENABLE_OVERLOADING)
    DrawContextDisplayPropertyInfo          ,
#endif
    constructDrawContextDisplay             ,
#if defined(ENABLE_OVERLOADING)
    drawContextDisplay                      ,
#endif
    getDrawContextDisplay                   ,


-- ** surface #attr:surface#
-- | The @GdkSurface@ the context is bound to.

#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.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.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 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

-- | Memory-managed wrapper type.
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
/= :: DrawContext -> DrawContext -> Bool
$c/= :: DrawContext -> DrawContext -> Bool
== :: DrawContext -> DrawContext -> Bool
$c== :: 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

-- | Type class for types which can be safely cast to `DrawContext`, for instance with `toDrawContext`.
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]

-- | Cast to `DrawContext`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
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 (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

-- | Convert 'DrawContext' to and from 'Data.GI.Base.GValue.GValue'. See 'Data.GI.Base.GValue.toGValue' and 'Data.GI.Base.GValue.fromGValue'.
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 (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 :: *) :: * 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

-- VVV Prop "display"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Display"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@display@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' drawContext #display
-- @
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 (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

-- | Construct a `GValueConstruct` with valid value for the “@display@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
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 (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 (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.4/docs/GI-Gdk-Objects-DrawContext.html#g:attr:display"
        })
#endif

-- VVV Prop "surface"
   -- Type: TInterface (Name {namespace = "Gdk", name = "Surface"})
   -- Flags: [PropertyReadable,PropertyWritable,PropertyConstructOnly]
   -- Nullable: (Just True,Nothing)

-- | Get the value of the “@surface@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' drawContext #surface
-- @
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 (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

-- | Construct a `GValueConstruct` with valid value for the “@surface@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
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 (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 (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.4/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, *)])
#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, *)])

#endif

-- method DrawContext::begin_frame
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DrawContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the `GdkDrawContext` used to draw the frame"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "region"
--           , argType =
--               TInterface Name { namespace = "cairo" , name = "Region" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "minimum region that should be drawn"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_draw_context_begin_frame" gdk_draw_context_begin_frame :: 
    Ptr DrawContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DrawContext"})
    Ptr Cairo.Region.Region ->              -- region : TInterface (Name {namespace = "cairo", name = "Region"})
    IO ()

-- | Indicates that you are beginning the process of redrawing /@region@/
-- on the /@context@/\'s surface.
-- 
-- Calling this function begins a drawing operation using /@context@/ on the
-- surface that /@context@/ was created from. The actual requirements and
-- guarantees for the drawing operation vary for different implementations
-- of drawing, so a t'GI.Gdk.Objects.CairoContext.CairoContext' and a t'GI.Gdk.Objects.GLContext.GLContext'
-- need to be treated differently.
-- 
-- A call to this function is a requirement for drawing and must be
-- followed by a call to 'GI.Gdk.Objects.DrawContext.drawContextEndFrame', which will
-- complete the drawing operation and ensure the contents become visible
-- on screen.
-- 
-- Note that the /@region@/ passed to this function is the minimum region that
-- needs to be drawn and depending on implementation, windowing system and
-- hardware in use, it might be necessary to draw a larger region. Drawing
-- implementation must use 'GI.Gdk.Objects.DrawContext.drawContextGetFrameRegion' to
-- query the region that must be drawn.
-- 
-- When using GTK, the widget system automatically places calls to
-- 'GI.Gdk.Objects.DrawContext.drawContextBeginFrame' and 'GI.Gdk.Objects.DrawContext.drawContextEndFrame' via the
-- use of @/Gsk.Renderer/@s, so application code does not need to call
-- these functions explicitly.
drawContextBeginFrame ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
    a
    -- ^ /@context@/: the @GdkDrawContext@ used to draw the frame
    -> Cairo.Region.Region
    -- ^ /@region@/: minimum region that should be drawn
    -> m ()
drawContextBeginFrame :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> Region -> m ()
drawContextBeginFrame a
context Region
region = IO () -> m ()
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 (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.4/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextBeginFrame"
        })


#endif

-- method DrawContext::end_frame
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DrawContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDrawContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_draw_context_end_frame" gdk_draw_context_end_frame :: 
    Ptr DrawContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DrawContext"})
    IO ()

-- | Ends a drawing operation started with 'GI.Gdk.Objects.DrawContext.drawContextBeginFrame'.
-- 
-- This makes the drawing available on screen.
-- See 'GI.Gdk.Objects.DrawContext.drawContextBeginFrame' for more details about drawing.
-- 
-- When using a t'GI.Gdk.Objects.GLContext.GLContext', this function may call @glFlush()@
-- implicitly before returning; it is not recommended to call @glFlush()@
-- explicitly before calling this function.
drawContextEndFrame ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
    a
    -- ^ /@context@/: a @GdkDrawContext@
    -> m ()
drawContextEndFrame :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m ()
drawContextEndFrame a
context = IO () -> m ()
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 (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.4/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextEndFrame"
        })


#endif

-- method DrawContext::get_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DrawContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDrawContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Display" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_draw_context_get_display" gdk_draw_context_get_display :: 
    Ptr DrawContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DrawContext"})
    IO (Ptr Gdk.Display.Display)

-- | Retrieves the @GdkDisplay@ the /@context@/ is created for
drawContextGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
    a
    -- ^ /@context@/: a @GdkDrawContext@
    -> m (Maybe Gdk.Display.Display)
    -- ^ __Returns:__ the @GdkDisplay@
drawContextGetDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m (Maybe Display)
drawContextGetDisplay a
context = IO (Maybe Display) -> m (Maybe Display)
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 (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 (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.4/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextGetDisplay"
        })


#endif

-- method DrawContext::get_frame_region
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DrawContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDrawContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "cairo" , name = "Region" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_draw_context_get_frame_region" gdk_draw_context_get_frame_region :: 
    Ptr DrawContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DrawContext"})
    IO (Ptr Cairo.Region.Region)

-- | Retrieves the region that is currently being repainted.
-- 
-- After a call to 'GI.Gdk.Objects.DrawContext.drawContextBeginFrame' this function will
-- return a union of the region passed to that function and the area of the
-- surface that the /@context@/ determined needs to be repainted.
-- 
-- If /@context@/ is not in between calls to 'GI.Gdk.Objects.DrawContext.drawContextBeginFrame'
-- and 'GI.Gdk.Objects.DrawContext.drawContextEndFrame', 'P.Nothing' will be returned.
drawContextGetFrameRegion ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
    a
    -- ^ /@context@/: a @GdkDrawContext@
    -> m (Maybe Cairo.Region.Region)
    -- ^ __Returns:__ a Cairo region
drawContextGetFrameRegion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m (Maybe Region)
drawContextGetFrameRegion a
context = IO (Maybe Region) -> m (Maybe Region)
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 (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 (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.4/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextGetFrameRegion"
        })


#endif

-- method DrawContext::get_surface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DrawContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDrawContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "Surface" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_draw_context_get_surface" gdk_draw_context_get_surface :: 
    Ptr DrawContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DrawContext"})
    IO (Ptr Gdk.Surface.Surface)

-- | Retrieves the surface that /@context@/ is bound to.
drawContextGetSurface ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
    a
    -- ^ /@context@/: a @GdkDrawContext@
    -> m (Maybe Gdk.Surface.Surface)
    -- ^ __Returns:__ a @GdkSurface@
drawContextGetSurface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m (Maybe Surface)
drawContextGetSurface a
context = IO (Maybe Surface) -> m (Maybe Surface)
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 (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 (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.4/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextGetSurface"
        })


#endif

-- method DrawContext::is_in_frame
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "DrawContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkDrawContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Just (TBasicType TBoolean)
-- throws : False
-- Skip return : False

foreign import ccall "gdk_draw_context_is_in_frame" gdk_draw_context_is_in_frame :: 
    Ptr DrawContext ->                      -- context : TInterface (Name {namespace = "Gdk", name = "DrawContext"})
    IO CInt

-- | Returns 'P.True' if /@context@/ is in the process of drawing to its surface.
-- 
-- This is the case between calls to 'GI.Gdk.Objects.DrawContext.drawContextBeginFrame'
-- and 'GI.Gdk.Objects.DrawContext.drawContextEndFrame'. In this situation, drawing commands
-- may be effecting the contents of the /@context@/\'s surface.
drawContextIsInFrame ::
    (B.CallStack.HasCallStack, MonadIO m, IsDrawContext a) =>
    a
    -- ^ /@context@/: a @GdkDrawContext@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the context is between 'GI.Gdk.Objects.DrawContext.drawContextBeginFrame'
    --   and 'GI.Gdk.Objects.DrawContext.drawContextEndFrame' calls.
drawContextIsInFrame :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsDrawContext a) =>
a -> m Bool
drawContextIsInFrame a
context = IO Bool -> m Bool
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 (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.4/docs/GI-Gdk-Objects-DrawContext.html#v:drawContextIsInFrame"
        })


#endif