{-# 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                        ,
    noDrawingContext                        ,
 
#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.ManagedPtr as B.ManagedPtr
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 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 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
newtype DrawingContext = DrawingContext (ManagedPtr DrawingContext)
    deriving (DrawingContext -> DrawingContext -> Bool
(DrawingContext -> DrawingContext -> Bool)
-> (DrawingContext -> DrawingContext -> Bool) -> Eq DrawingContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DrawingContext -> DrawingContext -> Bool
$c/= :: DrawingContext -> DrawingContext -> Bool
== :: DrawingContext -> DrawingContext -> Bool
$c== :: DrawingContext -> DrawingContext -> Bool
Eq)
foreign import ccall "gdk_drawing_context_get_type"
    c_gdk_drawing_context_get_type :: IO GType
instance GObject DrawingContext where
    gobjectType :: IO GType
gobjectType = IO GType
c_gdk_drawing_context_get_type
    
instance B.GValue.IsGValue DrawingContext where
    toGValue :: DrawingContext -> IO GValue
toGValue o :: DrawingContext
o = do
        GType
gtype <- IO GType
c_gdk_drawing_context_get_type
        DrawingContext -> (Ptr DrawingContext -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr DrawingContext
o (GType
-> (GValue -> Ptr DrawingContext -> IO ())
-> Ptr DrawingContext
-> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr DrawingContext -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO DrawingContext
fromGValue gv :: GValue
gv = do
        Ptr DrawingContext
ptr <- GValue -> IO (Ptr DrawingContext)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr DrawingContext)
        (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
        
    
class (GObject o, O.IsDescendantOf DrawingContext o) => IsDrawingContext o
instance (GObject o, O.IsDescendantOf DrawingContext o) => IsDrawingContext o
instance O.HasParentTypes DrawingContext
type instance O.ParentTypes DrawingContext = '[GObject.Object.Object]
toDrawingContext :: (MonadIO m, IsDrawingContext o) => o -> m DrawingContext
toDrawingContext :: o -> m DrawingContext
toDrawingContext = IO DrawingContext -> m DrawingContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr DrawingContext -> DrawingContext
DrawingContext
noDrawingContext :: Maybe DrawingContext
noDrawingContext :: Maybe DrawingContext
noDrawingContext = Maybe DrawingContext
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveDrawingContextMethod (t :: Symbol) (o :: *) :: * 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.MethodInfo 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
#endif
   
   
   
getDrawingContextClip :: (MonadIO m, IsDrawingContext o) => o -> m (Maybe Cairo.Region.Region)
getDrawingContextClip :: o -> m (Maybe Region)
getDrawingContextClip obj :: o
obj = 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
$ o -> String -> (ManagedPtr Region -> Region) -> IO (Maybe Region)
forall a b.
(GObject a, BoxedObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyBoxed o
obj "clip" ManagedPtr Region -> Region
Cairo.Region.Region
constructDrawingContextClip :: (IsDrawingContext o) => Cairo.Region.Region -> IO (GValueConstruct o)
constructDrawingContextClip :: Region -> IO (GValueConstruct o)
constructDrawingContextClip val :: Region
val = String -> Maybe Region -> IO (GValueConstruct o)
forall a o.
BoxedObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyBoxed "clip" (Region -> Maybe Region
forall a. a -> Maybe a
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
#endif
   
   
   
getDrawingContextWindow :: (MonadIO m, IsDrawingContext o) => o -> m Gdk.Window.Window
getDrawingContextWindow :: o -> m Window
getDrawingContextWindow obj :: o
obj = IO Window -> m Window
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
$ Text -> IO (Maybe Window) -> IO Window
forall a. HasCallStack => Text -> IO (Maybe a) -> IO a
checkUnexpectedNothing "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 "window" ManagedPtr Window -> Window
Gdk.Window.Window
constructDrawingContextWindow :: (IsDrawingContext o, Gdk.Window.IsWindow a) => a -> IO (GValueConstruct o)
constructDrawingContextWindow :: a -> IO (GValueConstruct o)
constructDrawingContextWindow val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "window" (a -> Maybe a
forall a. a -> Maybe a
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
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList DrawingContext
type instance O.AttributeList DrawingContext = DrawingContextAttributeList
type DrawingContextAttributeList = ('[ '("clip", DrawingContextClipPropertyInfo), '("window", DrawingContextWindowPropertyInfo)] :: [(Symbol, *)])
#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, *)])
#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 :: a -> m Context
drawingContextGetCairoContext context :: a
context = IO Context -> m Context
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 "drawingContextGetCairoContext" Ptr Context
result
    Context
result' <- ((ManagedPtr Context -> Context) -> Ptr Context -> IO Context
forall a.
(HasCallStack, BoxedObject 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 (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.MethodInfo DrawingContextGetCairoContextMethodInfo a signature where
    overloadedMethod = 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 :: a -> m (Maybe Region)
drawingContextGetClip context :: 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 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
$ \result' :: Ptr Region
result' -> do
        Region
result'' <- ((ManagedPtr Region -> Region) -> Ptr Region -> IO Region
forall a.
(HasCallStack, BoxedObject a) =>
(ManagedPtr a -> a) -> Ptr a -> IO a
wrapBoxed 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 DrawingContextGetClipMethodInfo
instance (signature ~ (m (Maybe Cairo.Region.Region)), MonadIO m, IsDrawingContext a) => O.MethodInfo DrawingContextGetClipMethodInfo a signature where
    overloadedMethod = 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 :: a -> m Window
drawingContextGetWindow context :: a
context = IO Window -> m Window
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 "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 (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.MethodInfo DrawingContextGetWindowMethodInfo a signature where
    overloadedMethod = 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 :: a -> m Bool
drawingContextIsValid context :: 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 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
/= 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 DrawingContextIsValidMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsDrawingContext a) => O.MethodInfo DrawingContextIsValidMethodInfo a signature where
    overloadedMethod = drawingContextIsValid
#endif