{-# LANGUAGE TypeApplications #-}


-- | Copyright  : Will Thompson and Iñaki García Etxebarria
-- License    : LGPL-2.1
-- Maintainer : Iñaki García Etxebarria
-- 
-- @GdkGLContext@ is an object representing a platform-specific
-- OpenGL draw context.
-- 
-- @GdkGLContext@s are created for a surface using
-- 'GI.Gdk.Objects.Surface.surfaceCreateGlContext', and the context will match
-- the characteristics of the surface.
-- 
-- A @GdkGLContext@ is not tied to any particular normal framebuffer.
-- For instance, it cannot draw to the surface back buffer. The GDK
-- repaint system is in full control of the painting to that. Instead,
-- you can create render buffers or textures and use [func/@cairoDrawFromGl@/]
-- in the draw function of your widget to draw them. Then GDK will handle
-- the integration of your rendering with that of other widgets.
-- 
-- Support for @GdkGLContext@ is platform-specific and context creation
-- can fail, returning 'P.Nothing' context.
-- 
-- A @GdkGLContext@ has to be made \"current\" in order to start using
-- it, otherwise any OpenGL call will be ignored.
-- 
-- == Creating a new OpenGL context
-- 
-- In order to create a new @GdkGLContext@ instance you need a @GdkSurface@,
-- which you typically get during the realize call of a widget.
-- 
-- A @GdkGLContext@ is not realized until either 'GI.Gdk.Objects.GLContext.gLContextMakeCurrent'
-- or 'GI.Gdk.Objects.GLContext.gLContextRealize' is called. It is possible to specify
-- details of the GL context like the OpenGL version to be used, or whether
-- the GL context should have extra state validation enabled after calling
-- 'GI.Gdk.Objects.Surface.surfaceCreateGlContext' by calling 'GI.Gdk.Objects.GLContext.gLContextRealize'.
-- If the realization fails you have the option to change the settings of
-- the @GdkGLContext@ and try again.
-- 
-- == Using a GdkGLContext
-- 
-- You will need to make the @GdkGLContext@ the current context before issuing
-- OpenGL calls; the system sends OpenGL commands to whichever context is current.
-- It is possible to have multiple contexts, so you always need to ensure that
-- the one which you want to draw with is the current one before issuing commands:
-- 
-- 
-- === /c code/
-- >gdk_gl_context_make_current (context);
-- 
-- 
-- You can now perform your drawing using OpenGL commands.
-- 
-- You can check which @GdkGLContext@ is the current one by using
-- [func/@gdk@/.GLContext.get_current]; you can also unset any @GdkGLContext@
-- that is currently set by calling [func/@gdk@/.GLContext.clear_current].

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

module GI.Gdk.Objects.GLContext
    ( 

-- * Exported types
    GLContext(..)                           ,
    IsGLContext                             ,
    toGLContext                             ,


 -- * 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"), [isLegacy]("GI.Gdk.Objects.GLContext#g:method:isLegacy"), [isShared]("GI.Gdk.Objects.GLContext#g:method:isShared"), [makeCurrent]("GI.Gdk.Objects.GLContext#g:method:makeCurrent"), [notify]("GI.GObject.Objects.Object#g:method:notify"), [notifyByPspec]("GI.GObject.Objects.Object#g:method:notifyByPspec"), [realize]("GI.Gdk.Objects.GLContext#g:method:realize"), [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
-- [getAllowedApis]("GI.Gdk.Objects.GLContext#g:method:getAllowedApis"), [getApi]("GI.Gdk.Objects.GLContext#g:method:getApi"), [getData]("GI.GObject.Objects.Object#g:method:getData"), [getDebugEnabled]("GI.Gdk.Objects.GLContext#g:method:getDebugEnabled"), [getDisplay]("GI.Gdk.Objects.GLContext#g:method:getDisplay"), [getForwardCompatible]("GI.Gdk.Objects.GLContext#g:method:getForwardCompatible"), [getFrameRegion]("GI.Gdk.Objects.DrawContext#g:method:getFrameRegion"), [getProperty]("GI.GObject.Objects.Object#g:method:getProperty"), [getQdata]("GI.GObject.Objects.Object#g:method:getQdata"), [getRequiredVersion]("GI.Gdk.Objects.GLContext#g:method:getRequiredVersion"), [getSharedContext]("GI.Gdk.Objects.GLContext#g:method:getSharedContext"), [getSurface]("GI.Gdk.Objects.GLContext#g:method:getSurface"), [getUseEs]("GI.Gdk.Objects.GLContext#g:method:getUseEs"), [getVersion]("GI.Gdk.Objects.GLContext#g:method:getVersion").
-- 
-- ==== Setters
-- [setAllowedApis]("GI.Gdk.Objects.GLContext#g:method:setAllowedApis"), [setData]("GI.GObject.Objects.Object#g:method:setData"), [setDataFull]("GI.GObject.Objects.Object#g:method:setDataFull"), [setDebugEnabled]("GI.Gdk.Objects.GLContext#g:method:setDebugEnabled"), [setForwardCompatible]("GI.Gdk.Objects.GLContext#g:method:setForwardCompatible"), [setProperty]("GI.GObject.Objects.Object#g:method:setProperty"), [setRequiredVersion]("GI.Gdk.Objects.GLContext#g:method:setRequiredVersion"), [setUseEs]("GI.Gdk.Objects.GLContext#g:method:setUseEs").

#if defined(ENABLE_OVERLOADING)
    ResolveGLContextMethod                  ,
#endif

-- ** clearCurrent #method:clearCurrent#

    gLContextClearCurrent                   ,


-- ** getAllowedApis #method:getAllowedApis#

#if defined(ENABLE_OVERLOADING)
    GLContextGetAllowedApisMethodInfo       ,
#endif
    gLContextGetAllowedApis                 ,


-- ** getApi #method:getApi#

#if defined(ENABLE_OVERLOADING)
    GLContextGetApiMethodInfo               ,
#endif
    gLContextGetApi                         ,


-- ** getCurrent #method:getCurrent#

    gLContextGetCurrent                     ,


-- ** getDebugEnabled #method:getDebugEnabled#

#if defined(ENABLE_OVERLOADING)
    GLContextGetDebugEnabledMethodInfo      ,
#endif
    gLContextGetDebugEnabled                ,


-- ** getDisplay #method:getDisplay#

#if defined(ENABLE_OVERLOADING)
    GLContextGetDisplayMethodInfo           ,
#endif
    gLContextGetDisplay                     ,


-- ** getForwardCompatible #method:getForwardCompatible#

#if defined(ENABLE_OVERLOADING)
    GLContextGetForwardCompatibleMethodInfo ,
#endif
    gLContextGetForwardCompatible           ,


-- ** getRequiredVersion #method:getRequiredVersion#

#if defined(ENABLE_OVERLOADING)
    GLContextGetRequiredVersionMethodInfo   ,
#endif
    gLContextGetRequiredVersion             ,


-- ** getSharedContext #method:getSharedContext#

#if defined(ENABLE_OVERLOADING)
    GLContextGetSharedContextMethodInfo     ,
#endif
    gLContextGetSharedContext               ,


-- ** getSurface #method:getSurface#

#if defined(ENABLE_OVERLOADING)
    GLContextGetSurfaceMethodInfo           ,
#endif
    gLContextGetSurface                     ,


-- ** getUseEs #method:getUseEs#

#if defined(ENABLE_OVERLOADING)
    GLContextGetUseEsMethodInfo             ,
#endif
    gLContextGetUseEs                       ,


-- ** getVersion #method:getVersion#

#if defined(ENABLE_OVERLOADING)
    GLContextGetVersionMethodInfo           ,
#endif
    gLContextGetVersion                     ,


-- ** isLegacy #method:isLegacy#

#if defined(ENABLE_OVERLOADING)
    GLContextIsLegacyMethodInfo             ,
#endif
    gLContextIsLegacy                       ,


-- ** isShared #method:isShared#

#if defined(ENABLE_OVERLOADING)
    GLContextIsSharedMethodInfo             ,
#endif
    gLContextIsShared                       ,


-- ** makeCurrent #method:makeCurrent#

#if defined(ENABLE_OVERLOADING)
    GLContextMakeCurrentMethodInfo          ,
#endif
    gLContextMakeCurrent                    ,


-- ** realize #method:realize#

#if defined(ENABLE_OVERLOADING)
    GLContextRealizeMethodInfo              ,
#endif
    gLContextRealize                        ,


-- ** setAllowedApis #method:setAllowedApis#

#if defined(ENABLE_OVERLOADING)
    GLContextSetAllowedApisMethodInfo       ,
#endif
    gLContextSetAllowedApis                 ,


-- ** setDebugEnabled #method:setDebugEnabled#

#if defined(ENABLE_OVERLOADING)
    GLContextSetDebugEnabledMethodInfo      ,
#endif
    gLContextSetDebugEnabled                ,


-- ** setForwardCompatible #method:setForwardCompatible#

#if defined(ENABLE_OVERLOADING)
    GLContextSetForwardCompatibleMethodInfo ,
#endif
    gLContextSetForwardCompatible           ,


-- ** setRequiredVersion #method:setRequiredVersion#

#if defined(ENABLE_OVERLOADING)
    GLContextSetRequiredVersionMethodInfo   ,
#endif
    gLContextSetRequiredVersion             ,


-- ** setUseEs #method:setUseEs#

#if defined(ENABLE_OVERLOADING)
    GLContextSetUseEsMethodInfo             ,
#endif
    gLContextSetUseEs                       ,




 -- * Properties


-- ** allowedApis #attr:allowedApis#
-- | The allowed APIs.
-- 
-- /Since: 4.6/

#if defined(ENABLE_OVERLOADING)
    GLContextAllowedApisPropertyInfo        ,
#endif
    constructGLContextAllowedApis           ,
#if defined(ENABLE_OVERLOADING)
    gLContextAllowedApis                    ,
#endif
    getGLContextAllowedApis                 ,
    setGLContextAllowedApis                 ,


-- ** api #attr:api#
-- | The API currently in use.
-- 
-- /Since: 4.6/

#if defined(ENABLE_OVERLOADING)
    GLContextApiPropertyInfo                ,
#endif
#if defined(ENABLE_OVERLOADING)
    gLContextApi                            ,
#endif
    getGLContextApi                         ,


-- ** sharedContext #attr:sharedContext#
-- | Always 'P.Nothing'
-- 
-- As many contexts can share data now and no single shared context exists
-- anymore, this function has been deprecated and now always returns 'P.Nothing'.

#if defined(ENABLE_OVERLOADING)
    GLContextSharedContextPropertyInfo      ,
#endif
    constructGLContextSharedContext         ,
#if defined(ENABLE_OVERLOADING)
    gLContextSharedContext                  ,
#endif
    getGLContextSharedContext               ,




    ) 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 GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Flags as Gdk.Flags
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.DrawContext as Gdk.DrawContext
import {-# SOURCE #-} qualified GI.Gdk.Objects.Surface as Gdk.Surface

-- | Memory-managed wrapper type.
newtype GLContext = GLContext (SP.ManagedPtr GLContext)
    deriving (GLContext -> GLContext -> Bool
(GLContext -> GLContext -> Bool)
-> (GLContext -> GLContext -> Bool) -> Eq GLContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: GLContext -> GLContext -> Bool
== :: GLContext -> GLContext -> Bool
$c/= :: GLContext -> GLContext -> Bool
/= :: GLContext -> GLContext -> Bool
Eq)

instance SP.ManagedPtrNewtype GLContext where
    toManagedPtr :: GLContext -> ManagedPtr GLContext
toManagedPtr (GLContext ManagedPtr GLContext
p) = ManagedPtr GLContext
p

foreign import ccall "gdk_gl_context_get_type"
    c_gdk_gl_context_get_type :: IO B.Types.GType

instance B.Types.TypedObject GLContext where
    glibType :: IO GType
glibType = IO GType
c_gdk_gl_context_get_type

instance B.Types.GObject GLContext

-- | Type class for types which can be safely cast to `GLContext`, for instance with `toGLContext`.
class (SP.GObject o, O.IsDescendantOf GLContext o) => IsGLContext o
instance (SP.GObject o, O.IsDescendantOf GLContext o) => IsGLContext o

instance O.HasParentTypes GLContext
type instance O.ParentTypes GLContext = '[Gdk.DrawContext.DrawContext, GObject.Object.Object]

-- | Cast to `GLContext`, for types for which this is known to be safe. For general casts, use `Data.GI.Base.ManagedPtr.castTo`.
toGLContext :: (MIO.MonadIO m, IsGLContext o) => o -> m GLContext
toGLContext :: forall (m :: * -> *) o.
(MonadIO m, IsGLContext o) =>
o -> m GLContext
toGLContext = IO GLContext -> m GLContext
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO GLContext -> m GLContext)
-> (o -> IO GLContext) -> o -> m GLContext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ManagedPtr GLContext -> GLContext) -> o -> IO GLContext
forall o o'.
(HasCallStack, ManagedPtrNewtype o, TypedObject o,
 ManagedPtrNewtype o', TypedObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
B.ManagedPtr.unsafeCastTo ManagedPtr GLContext -> GLContext
GLContext

-- | Convert 'GLContext' 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 GLContext) where
    gvalueGType_ :: IO GType
gvalueGType_ = IO GType
c_gdk_gl_context_get_type
    gvalueSet_ :: Ptr GValue -> Maybe GLContext -> IO ()
gvalueSet_ Ptr GValue
gv Maybe GLContext
P.Nothing = Ptr GValue -> Ptr GLContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv (Ptr GLContext
forall a. Ptr a
FP.nullPtr :: FP.Ptr GLContext)
    gvalueSet_ Ptr GValue
gv (P.Just GLContext
obj) = GLContext -> (Ptr GLContext -> IO ()) -> IO ()
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GLContext
obj (Ptr GValue -> Ptr GLContext -> IO ()
forall a. GObject a => Ptr GValue -> Ptr a -> IO ()
B.GValue.set_object Ptr GValue
gv)
    gvalueGet_ :: Ptr GValue -> IO (Maybe GLContext)
gvalueGet_ Ptr GValue
gv = do
        Ptr GLContext
ptr <- Ptr GValue -> IO (Ptr GLContext)
forall a. GObject a => Ptr GValue -> IO (Ptr a)
B.GValue.get_object Ptr GValue
gv :: IO (FP.Ptr GLContext)
        if Ptr GLContext
ptr Ptr GLContext -> Ptr GLContext -> Bool
forall a. Eq a => a -> a -> Bool
/= Ptr GLContext
forall a. Ptr a
FP.nullPtr
        then GLContext -> Maybe GLContext
forall a. a -> Maybe a
P.Just (GLContext -> Maybe GLContext)
-> IO GLContext -> IO (Maybe GLContext)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ManagedPtr GLContext -> GLContext)
-> Ptr GLContext -> IO GLContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
B.ManagedPtr.newObject ManagedPtr GLContext -> GLContext
GLContext Ptr GLContext
ptr
        else Maybe GLContext -> IO (Maybe GLContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GLContext
forall a. Maybe a
P.Nothing
        
    

#if defined(ENABLE_OVERLOADING)
type family ResolveGLContextMethod (t :: Symbol) (o :: DK.Type) :: DK.Type where
    ResolveGLContextMethod "beginFrame" o = Gdk.DrawContext.DrawContextBeginFrameMethodInfo
    ResolveGLContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGLContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    ResolveGLContextMethod "endFrame" o = Gdk.DrawContext.DrawContextEndFrameMethodInfo
    ResolveGLContextMethod "forceFloating" o = GObject.Object.ObjectForceFloatingMethodInfo
    ResolveGLContextMethod "freezeNotify" o = GObject.Object.ObjectFreezeNotifyMethodInfo
    ResolveGLContextMethod "getv" o = GObject.Object.ObjectGetvMethodInfo
    ResolveGLContextMethod "isFloating" o = GObject.Object.ObjectIsFloatingMethodInfo
    ResolveGLContextMethod "isInFrame" o = Gdk.DrawContext.DrawContextIsInFrameMethodInfo
    ResolveGLContextMethod "isLegacy" o = GLContextIsLegacyMethodInfo
    ResolveGLContextMethod "isShared" o = GLContextIsSharedMethodInfo
    ResolveGLContextMethod "makeCurrent" o = GLContextMakeCurrentMethodInfo
    ResolveGLContextMethod "notify" o = GObject.Object.ObjectNotifyMethodInfo
    ResolveGLContextMethod "notifyByPspec" o = GObject.Object.ObjectNotifyByPspecMethodInfo
    ResolveGLContextMethod "realize" o = GLContextRealizeMethodInfo
    ResolveGLContextMethod "ref" o = GObject.Object.ObjectRefMethodInfo
    ResolveGLContextMethod "refSink" o = GObject.Object.ObjectRefSinkMethodInfo
    ResolveGLContextMethod "runDispose" o = GObject.Object.ObjectRunDisposeMethodInfo
    ResolveGLContextMethod "stealData" o = GObject.Object.ObjectStealDataMethodInfo
    ResolveGLContextMethod "stealQdata" o = GObject.Object.ObjectStealQdataMethodInfo
    ResolveGLContextMethod "thawNotify" o = GObject.Object.ObjectThawNotifyMethodInfo
    ResolveGLContextMethod "unref" o = GObject.Object.ObjectUnrefMethodInfo
    ResolveGLContextMethod "watchClosure" o = GObject.Object.ObjectWatchClosureMethodInfo
    ResolveGLContextMethod "getAllowedApis" o = GLContextGetAllowedApisMethodInfo
    ResolveGLContextMethod "getApi" o = GLContextGetApiMethodInfo
    ResolveGLContextMethod "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGLContextMethod "getDebugEnabled" o = GLContextGetDebugEnabledMethodInfo
    ResolveGLContextMethod "getDisplay" o = GLContextGetDisplayMethodInfo
    ResolveGLContextMethod "getForwardCompatible" o = GLContextGetForwardCompatibleMethodInfo
    ResolveGLContextMethod "getFrameRegion" o = Gdk.DrawContext.DrawContextGetFrameRegionMethodInfo
    ResolveGLContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGLContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGLContextMethod "getRequiredVersion" o = GLContextGetRequiredVersionMethodInfo
    ResolveGLContextMethod "getSharedContext" o = GLContextGetSharedContextMethodInfo
    ResolveGLContextMethod "getSurface" o = GLContextGetSurfaceMethodInfo
    ResolveGLContextMethod "getUseEs" o = GLContextGetUseEsMethodInfo
    ResolveGLContextMethod "getVersion" o = GLContextGetVersionMethodInfo
    ResolveGLContextMethod "setAllowedApis" o = GLContextSetAllowedApisMethodInfo
    ResolveGLContextMethod "setData" o = GObject.Object.ObjectSetDataMethodInfo
    ResolveGLContextMethod "setDataFull" o = GObject.Object.ObjectSetDataFullMethodInfo
    ResolveGLContextMethod "setDebugEnabled" o = GLContextSetDebugEnabledMethodInfo
    ResolveGLContextMethod "setForwardCompatible" o = GLContextSetForwardCompatibleMethodInfo
    ResolveGLContextMethod "setProperty" o = GObject.Object.ObjectSetPropertyMethodInfo
    ResolveGLContextMethod "setRequiredVersion" o = GLContextSetRequiredVersionMethodInfo
    ResolveGLContextMethod "setUseEs" o = GLContextSetUseEsMethodInfo
    ResolveGLContextMethod l o = O.MethodResolutionFailed l o

instance (info ~ ResolveGLContextMethod t GLContext, O.OverloadedMethod info GLContext p) => OL.IsLabel t (GLContext -> 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 ~ ResolveGLContextMethod t GLContext, O.OverloadedMethod info GLContext p, R.HasField t GLContext p) => R.HasField t GLContext p where
    getField = O.overloadedMethod @info

#endif

instance (info ~ ResolveGLContextMethod t GLContext, O.OverloadedMethodInfo info GLContext) => OL.IsLabel t (O.MethodProxy info GLContext) where
#if MIN_VERSION_base(4,10,0)
    fromLabel = O.MethodProxy
#else
    fromLabel _ = O.MethodProxy
#endif

#endif

-- VVV Prop "allowed-apis"
   -- Type: TInterface (Name {namespace = "Gdk", name = "GLAPI"})
   -- Flags: [PropertyReadable,PropertyWritable]
   -- Nullable: (Just False,Just False)

-- | Get the value of the “@allowed-apis@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gLContext #allowedApis
-- @
getGLContextAllowedApis :: (MonadIO m, IsGLContext o) => o -> m [Gdk.Flags.GLAPI]
getGLContextAllowedApis :: forall (m :: * -> *) o.
(MonadIO m, IsGLContext o) =>
o -> m [GLAPI]
getGLContextAllowedApis o
obj = IO [GLAPI] -> m [GLAPI]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [GLAPI] -> m [GLAPI]) -> IO [GLAPI] -> m [GLAPI]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [GLAPI]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"allowed-apis"

-- | Set the value of the “@allowed-apis@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.set' gLContext [ #allowedApis 'Data.GI.Base.Attributes.:=' value ]
-- @
setGLContextAllowedApis :: (MonadIO m, IsGLContext o) => o -> [Gdk.Flags.GLAPI] -> m ()
setGLContextAllowedApis :: forall (m :: * -> *) o.
(MonadIO m, IsGLContext o) =>
o -> [GLAPI] -> m ()
setGLContextAllowedApis o
obj [GLAPI]
val = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    o -> String -> [GLAPI] -> IO ()
forall a b.
(IsGFlag b, BoxedFlags b, GObject a) =>
a -> String -> [b] -> IO ()
B.Properties.setObjectPropertyFlags o
obj String
"allowed-apis" [GLAPI]
val

-- | Construct a `GValueConstruct` with valid value for the “@allowed-apis@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGLContextAllowedApis :: (IsGLContext o, MIO.MonadIO m) => [Gdk.Flags.GLAPI] -> m (GValueConstruct o)
constructGLContextAllowedApis :: forall o (m :: * -> *).
(IsGLContext o, MonadIO m) =>
[GLAPI] -> m (GValueConstruct o)
constructGLContextAllowedApis [GLAPI]
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 -> [GLAPI] -> IO (GValueConstruct o)
forall a o.
(IsGFlag a, BoxedFlags a) =>
String -> [a] -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyFlags String
"allowed-apis" [GLAPI]
val

#if defined(ENABLE_OVERLOADING)
data GLContextAllowedApisPropertyInfo
instance AttrInfo GLContextAllowedApisPropertyInfo where
    type AttrAllowedOps GLContextAllowedApisPropertyInfo = '[ 'AttrSet, 'AttrConstruct, 'AttrGet]
    type AttrBaseTypeConstraint GLContextAllowedApisPropertyInfo = IsGLContext
    type AttrSetTypeConstraint GLContextAllowedApisPropertyInfo = (~) [Gdk.Flags.GLAPI]
    type AttrTransferTypeConstraint GLContextAllowedApisPropertyInfo = (~) [Gdk.Flags.GLAPI]
    type AttrTransferType GLContextAllowedApisPropertyInfo = [Gdk.Flags.GLAPI]
    type AttrGetType GLContextAllowedApisPropertyInfo = [Gdk.Flags.GLAPI]
    type AttrLabel GLContextAllowedApisPropertyInfo = "allowed-apis"
    type AttrOrigin GLContextAllowedApisPropertyInfo = GLContext
    attrGet = getGLContextAllowedApis
    attrSet = setGLContextAllowedApis
    attrTransfer _ v = do
        return v
    attrConstruct = constructGLContextAllowedApis
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.allowedApis"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#g:attr:allowedApis"
        })
#endif

-- VVV Prop "api"
   -- Type: TInterface (Name {namespace = "Gdk", name = "GLAPI"})
   -- Flags: [PropertyReadable]
   -- Nullable: (Just False,Nothing)

-- | Get the value of the “@api@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gLContext #api
-- @
getGLContextApi :: (MonadIO m, IsGLContext o) => o -> m [Gdk.Flags.GLAPI]
getGLContextApi :: forall (m :: * -> *) o.
(MonadIO m, IsGLContext o) =>
o -> m [GLAPI]
getGLContextApi o
obj = IO [GLAPI] -> m [GLAPI]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO [GLAPI] -> m [GLAPI]) -> IO [GLAPI] -> m [GLAPI]
forall a b. (a -> b) -> a -> b
$ o -> String -> IO [GLAPI]
forall a b.
(GObject a, IsGFlag b, BoxedFlags b) =>
a -> String -> IO [b]
B.Properties.getObjectPropertyFlags o
obj String
"api"

#if defined(ENABLE_OVERLOADING)
data GLContextApiPropertyInfo
instance AttrInfo GLContextApiPropertyInfo where
    type AttrAllowedOps GLContextApiPropertyInfo = '[ 'AttrGet]
    type AttrBaseTypeConstraint GLContextApiPropertyInfo = IsGLContext
    type AttrSetTypeConstraint GLContextApiPropertyInfo = (~) ()
    type AttrTransferTypeConstraint GLContextApiPropertyInfo = (~) ()
    type AttrTransferType GLContextApiPropertyInfo = ()
    type AttrGetType GLContextApiPropertyInfo = [Gdk.Flags.GLAPI]
    type AttrLabel GLContextApiPropertyInfo = "api"
    type AttrOrigin GLContextApiPropertyInfo = GLContext
    attrGet = getGLContextApi
    attrSet = undefined
    attrTransfer _ = undefined
    attrConstruct = undefined
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.api"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#g:attr:api"
        })
#endif

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

-- | Get the value of the “@shared-context@” property.
-- When <https://github.com/haskell-gi/haskell-gi/wiki/Overloading overloading> is enabled, this is equivalent to
-- 
-- @
-- 'Data.GI.Base.Attributes.get' gLContext #sharedContext
-- @
getGLContextSharedContext :: (MonadIO m, IsGLContext o) => o -> m (Maybe GLContext)
getGLContextSharedContext :: forall (m :: * -> *) o.
(MonadIO m, IsGLContext o) =>
o -> m (Maybe GLContext)
getGLContextSharedContext o
obj = IO (Maybe GLContext) -> m (Maybe GLContext)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe GLContext) -> m (Maybe GLContext))
-> IO (Maybe GLContext) -> m (Maybe GLContext)
forall a b. (a -> b) -> a -> b
$ o
-> String
-> (ManagedPtr GLContext -> GLContext)
-> IO (Maybe GLContext)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"shared-context" ManagedPtr GLContext -> GLContext
GLContext

-- | Construct a `GValueConstruct` with valid value for the “@shared-context@” property. This is rarely needed directly, but it is used by `Data.GI.Base.Constructible.new`.
constructGLContextSharedContext :: (IsGLContext o, MIO.MonadIO m, IsGLContext a) => a -> m (GValueConstruct o)
constructGLContextSharedContext :: forall o (m :: * -> *) a.
(IsGLContext o, MonadIO m, IsGLContext a) =>
a -> m (GValueConstruct o)
constructGLContextSharedContext 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
"shared-context" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)

#if defined(ENABLE_OVERLOADING)
data GLContextSharedContextPropertyInfo
instance AttrInfo GLContextSharedContextPropertyInfo where
    type AttrAllowedOps GLContextSharedContextPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint GLContextSharedContextPropertyInfo = IsGLContext
    type AttrSetTypeConstraint GLContextSharedContextPropertyInfo = IsGLContext
    type AttrTransferTypeConstraint GLContextSharedContextPropertyInfo = IsGLContext
    type AttrTransferType GLContextSharedContextPropertyInfo = GLContext
    type AttrGetType GLContextSharedContextPropertyInfo = (Maybe GLContext)
    type AttrLabel GLContextSharedContextPropertyInfo = "shared-context"
    type AttrOrigin GLContextSharedContextPropertyInfo = GLContext
    attrGet = getGLContextSharedContext
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo GLContext v
    attrConstruct = constructGLContextSharedContext
    attrClear = undefined
    dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.sharedContext"
        , O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#g:attr:sharedContext"
        })
#endif

#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GLContext
type instance O.AttributeList GLContext = GLContextAttributeList
type GLContextAttributeList = ('[ '("allowedApis", GLContextAllowedApisPropertyInfo), '("api", GLContextApiPropertyInfo), '("display", Gdk.DrawContext.DrawContextDisplayPropertyInfo), '("sharedContext", GLContextSharedContextPropertyInfo), '("surface", Gdk.DrawContext.DrawContextSurfacePropertyInfo)] :: [(Symbol, DK.Type)])
#endif

#if defined(ENABLE_OVERLOADING)
gLContextAllowedApis :: AttrLabelProxy "allowedApis"
gLContextAllowedApis = AttrLabelProxy

gLContextApi :: AttrLabelProxy "api"
gLContextApi = AttrLabelProxy

gLContextSharedContext :: AttrLabelProxy "sharedContext"
gLContextSharedContext = AttrLabelProxy

#endif

#if defined(ENABLE_OVERLOADING)
type instance O.SignalList GLContext = GLContextSignalList
type GLContextSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, DK.Type)])

#endif

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

foreign import ccall "gdk_gl_context_get_allowed_apis" gdk_gl_context_get_allowed_apis :: 
    Ptr GLContext ->                        -- self : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    IO CUInt

-- | Gets the allowed APIs set via 'GI.Gdk.Objects.GLContext.gLContextSetAllowedApis'.
-- 
-- /Since: 4.6/
gLContextGetAllowedApis ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@self@/: a GL context
    -> m [Gdk.Flags.GLAPI]
    -- ^ __Returns:__ the allowed APIs
gLContextGetAllowedApis :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m [GLAPI]
gLContextGetAllowedApis a
self = IO [GLAPI] -> m [GLAPI]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [GLAPI] -> m [GLAPI]) -> IO [GLAPI] -> m [GLAPI]
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
self' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr GLContext -> IO CUInt
gdk_gl_context_get_allowed_apis Ptr GLContext
self'
    let result' :: [GLAPI]
result' = CUInt -> [GLAPI]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    [GLAPI] -> IO [GLAPI]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [GLAPI]
result'

#if defined(ENABLE_OVERLOADING)
data GLContextGetAllowedApisMethodInfo
instance (signature ~ (m [Gdk.Flags.GLAPI]), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetAllowedApisMethodInfo a signature where
    overloadedMethod = gLContextGetAllowedApis

instance O.OverloadedMethodInfo GLContextGetAllowedApisMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetAllowedApis",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetAllowedApis"
        })


#endif

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

foreign import ccall "gdk_gl_context_get_api" gdk_gl_context_get_api :: 
    Ptr GLContext ->                        -- self : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    IO CUInt

-- | Gets the API currently in use.
-- 
-- If the renderer has not been realized yet, 0 is returned.
-- 
-- /Since: 4.6/
gLContextGetApi ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@self@/: a GL context
    -> m [Gdk.Flags.GLAPI]
    -- ^ __Returns:__ the currently used API
gLContextGetApi :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m [GLAPI]
gLContextGetApi a
self = IO [GLAPI] -> m [GLAPI]
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [GLAPI] -> m [GLAPI]) -> IO [GLAPI] -> m [GLAPI]
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
self' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    CUInt
result <- Ptr GLContext -> IO CUInt
gdk_gl_context_get_api Ptr GLContext
self'
    let result' :: [GLAPI]
result' = CUInt -> [GLAPI]
forall a b. (Storable a, Integral a, Bits a, IsGFlag b) => a -> [b]
wordToGFlags CUInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    [GLAPI] -> IO [GLAPI]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [GLAPI]
result'

#if defined(ENABLE_OVERLOADING)
data GLContextGetApiMethodInfo
instance (signature ~ (m [Gdk.Flags.GLAPI]), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetApiMethodInfo a signature where
    overloadedMethod = gLContextGetApi

instance O.OverloadedMethodInfo GLContextGetApiMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetApi",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetApi"
        })


#endif

-- method GLContext::get_debug_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , 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_gl_context_get_debug_enabled" gdk_gl_context_get_debug_enabled :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    IO CInt

-- | Retrieves whether the context is doing extra validations and runtime checking.
-- 
-- See 'GI.Gdk.Objects.GLContext.gLContextSetDebugEnabled'.
gLContextGetDebugEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if debugging is enabled
gLContextGetDebugEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m Bool
gLContextGetDebugEnabled 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 GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CInt
result <- Ptr GLContext -> IO CInt
gdk_gl_context_get_debug_enabled Ptr GLContext
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 GLContextGetDebugEnabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetDebugEnabledMethodInfo a signature where
    overloadedMethod = gLContextGetDebugEnabled

instance O.OverloadedMethodInfo GLContextGetDebugEnabledMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetDebugEnabled",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetDebugEnabled"
        })


#endif

-- method GLContext::get_display
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , 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_gl_context_get_display" gdk_gl_context_get_display :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    IO (Ptr Gdk.Display.Display)

-- | Retrieves the display the /@context@/ is created for
gLContextGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m (Maybe Gdk.Display.Display)
    -- ^ __Returns:__ a @GdkDisplay@
gLContextGetDisplay :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Maybe Display)
gLContextGetDisplay a
context = IO (Maybe Display) -> m (Maybe Display)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Display
result <- Ptr GLContext -> IO (Ptr Display)
gdk_gl_context_get_display Ptr GLContext
context'
    Maybe Display
maybeResult <- Ptr Display -> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Display
result ((Ptr Display -> IO Display) -> IO (Maybe Display))
-> (Ptr Display -> IO Display) -> IO (Maybe Display)
forall a b. (a -> b) -> a -> b
$ \Ptr Display
result' -> do
        Display
result'' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
result'
        Display -> IO Display
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Maybe Display -> IO (Maybe Display)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult

#if defined(ENABLE_OVERLOADING)
data GLContextGetDisplayMethodInfo
instance (signature ~ (m (Maybe Gdk.Display.Display)), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetDisplayMethodInfo a signature where
    overloadedMethod = gLContextGetDisplay

instance O.OverloadedMethodInfo GLContextGetDisplayMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetDisplay",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetDisplay"
        })


#endif

-- method GLContext::get_forward_compatible
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , 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_gl_context_get_forward_compatible" gdk_gl_context_get_forward_compatible :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    IO CInt

-- | Retrieves whether the context is forward-compatible.
-- 
-- See 'GI.Gdk.Objects.GLContext.gLContextSetForwardCompatible'.
gLContextGetForwardCompatible ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the context should be forward-compatible
gLContextGetForwardCompatible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m Bool
gLContextGetForwardCompatible 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 GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CInt
result <- Ptr GLContext -> IO CInt
gdk_gl_context_get_forward_compatible Ptr GLContext
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 GLContextGetForwardCompatibleMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetForwardCompatibleMethodInfo a signature where
    overloadedMethod = gLContextGetForwardCompatible

instance O.OverloadedMethodInfo GLContextGetForwardCompatibleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetForwardCompatible",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetForwardCompatible"
        })


#endif

-- method GLContext::get_required_version
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "major"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the major version to request"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "minor"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = True
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "return location for the minor version to request"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_gl_context_get_required_version" gdk_gl_context_get_required_version :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    Ptr Int32 ->                            -- major : TBasicType TInt
    Ptr Int32 ->                            -- minor : TBasicType TInt
    IO ()

-- | Retrieves required OpenGL version set as a requirement for the /@context@/
-- realization. It will not change even if a greater OpenGL version is supported
-- and used after the /@context@/ is realized. See
-- 'GI.Gdk.Objects.GLContext.gLContextGetVersion' for the real version in use.
-- 
-- See 'GI.Gdk.Objects.GLContext.gLContextSetRequiredVersion'.
gLContextGetRequiredVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m ((Int32, Int32))
gLContextGetRequiredVersion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Int32, Int32)
gLContextGetRequiredVersion a
context = IO (Int32, Int32) -> m (Int32, Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Int32
major <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
minor <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr GLContext -> Ptr Int32 -> Ptr Int32 -> IO ()
gdk_gl_context_get_required_version Ptr GLContext
context' Ptr Int32
major Ptr Int32
minor
    Int32
major' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
major
    Int32
minor' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
minor
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
major
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
minor
    (Int32, Int32) -> IO (Int32, Int32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
major', Int32
minor')

#if defined(ENABLE_OVERLOADING)
data GLContextGetRequiredVersionMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetRequiredVersionMethodInfo a signature where
    overloadedMethod = gLContextGetRequiredVersion

instance O.OverloadedMethodInfo GLContextGetRequiredVersionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetRequiredVersion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetRequiredVersion"
        })


#endif

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

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

{-# DEPRECATED gLContextGetSharedContext ["(Since version 4.4)","Use 'GI.Gdk.Objects.GLContext.gLContextIsShared' to check if contexts","  can be shared."] #-}
-- | Used to retrieves the @GdkGLContext@ that this /@context@/ share data with.
-- 
-- As many contexts can share data now and no single shared context exists
-- anymore, this function has been deprecated and now always returns 'P.Nothing'.
gLContextGetSharedContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m (Maybe GLContext)
    -- ^ __Returns:__ 'P.Nothing'
gLContextGetSharedContext :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Maybe GLContext)
gLContextGetSharedContext a
context = IO (Maybe GLContext) -> m (Maybe GLContext)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GLContext) -> m (Maybe GLContext))
-> IO (Maybe GLContext) -> m (Maybe GLContext)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr GLContext
result <- Ptr GLContext -> IO (Ptr GLContext)
gdk_gl_context_get_shared_context Ptr GLContext
context'
    Maybe GLContext
maybeResult <- Ptr GLContext
-> (Ptr GLContext -> IO GLContext) -> IO (Maybe GLContext)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GLContext
result ((Ptr GLContext -> IO GLContext) -> IO (Maybe GLContext))
-> (Ptr GLContext -> IO GLContext) -> IO (Maybe GLContext)
forall a b. (a -> b) -> a -> b
$ \Ptr GLContext
result' -> do
        GLContext
result'' <- ((ManagedPtr GLContext -> GLContext)
-> Ptr GLContext -> IO GLContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr GLContext -> GLContext
GLContext) Ptr GLContext
result'
        GLContext -> IO GLContext
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GLContext
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Maybe GLContext -> IO (Maybe GLContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GLContext
maybeResult

#if defined(ENABLE_OVERLOADING)
data GLContextGetSharedContextMethodInfo
instance (signature ~ (m (Maybe GLContext)), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetSharedContextMethodInfo a signature where
    overloadedMethod = gLContextGetSharedContext

instance O.OverloadedMethodInfo GLContextGetSharedContextMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetSharedContext",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetSharedContext"
        })


#endif

-- method GLContext::get_surface
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , 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_gl_context_get_surface" gdk_gl_context_get_surface :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    IO (Ptr Gdk.Surface.Surface)

-- | Retrieves the surface used by the /@context@/.
gLContextGetSurface ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m (Maybe Gdk.Surface.Surface)
    -- ^ __Returns:__ a @GdkSurface@
gLContextGetSurface :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Maybe Surface)
gLContextGetSurface a
context = IO (Maybe Surface) -> m (Maybe Surface)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Surface) -> m (Maybe Surface))
-> IO (Maybe Surface) -> m (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Surface
result <- Ptr GLContext -> IO (Ptr Surface)
gdk_gl_context_get_surface Ptr GLContext
context'
    Maybe Surface
maybeResult <- Ptr Surface -> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Surface
result ((Ptr Surface -> IO Surface) -> IO (Maybe Surface))
-> (Ptr Surface -> IO Surface) -> IO (Maybe Surface)
forall a b. (a -> b) -> a -> b
$ \Ptr Surface
result' -> do
        Surface
result'' <- ((ManagedPtr Surface -> Surface) -> Ptr Surface -> IO Surface
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Surface -> Surface
Gdk.Surface.Surface) Ptr Surface
result'
        Surface -> IO Surface
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Surface
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Maybe Surface -> IO (Maybe Surface)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Surface
maybeResult

#if defined(ENABLE_OVERLOADING)
data GLContextGetSurfaceMethodInfo
instance (signature ~ (m (Maybe Gdk.Surface.Surface)), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetSurfaceMethodInfo a signature where
    overloadedMethod = gLContextGetSurface

instance O.OverloadedMethodInfo GLContextGetSurfaceMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetSurface",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetSurface"
        })


#endif

-- method GLContext::get_use_es
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , 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_gl_context_get_use_es" gdk_gl_context_get_use_es :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    IO CInt

-- | Checks whether the /@context@/ is using an OpenGL or OpenGL ES profile.
gLContextGetUseEs ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the @GdkGLContext@ is using an OpenGL ES profile;
    -- 'P.False' if other profile is in use of if the /@context@/ has not yet
    -- been realized.
gLContextGetUseEs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m Bool
gLContextGetUseEs 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 GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CInt
result <- Ptr GLContext -> IO CInt
gdk_gl_context_get_use_es Ptr GLContext
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 GLContextGetUseEsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetUseEsMethodInfo a signature where
    overloadedMethod = gLContextGetUseEs

instance O.OverloadedMethodInfo GLContextGetUseEsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetUseEs",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetUseEs"
        })


#endif

-- method GLContext::get_version
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "major"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the major version"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       , Arg
--           { argCName = "minor"
--           , argType = TBasicType TInt
--           , direction = DirectionOut
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "return location for the minor version"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferEverything
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_gl_context_get_version" gdk_gl_context_get_version :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    Ptr Int32 ->                            -- major : TBasicType TInt
    Ptr Int32 ->                            -- minor : TBasicType TInt
    IO ()

-- | Retrieves the OpenGL version of the /@context@/.
-- 
-- The /@context@/ must be realized prior to calling this function.
-- 
-- If the /@context@/ has never been made current, the version cannot
-- be known and it will return 0 for both /@major@/ and /@minor@/.
gLContextGetVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m ((Int32, Int32))
gLContextGetVersion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Int32, Int32)
gLContextGetVersion a
context = IO (Int32, Int32) -> m (Int32, Int32)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int32, Int32) -> m (Int32, Int32))
-> IO (Int32, Int32) -> m (Int32, Int32)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr Int32
major <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr Int32
minor <- IO (Ptr Int32)
forall a. Storable a => IO (Ptr a)
allocMem :: IO (Ptr Int32)
    Ptr GLContext -> Ptr Int32 -> Ptr Int32 -> IO ()
gdk_gl_context_get_version Ptr GLContext
context' Ptr Int32
major Ptr Int32
minor
    Int32
major' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
major
    Int32
minor' <- Ptr Int32 -> IO Int32
forall a. Storable a => Ptr a -> IO a
peek Ptr Int32
minor
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
major
    Ptr Int32 -> IO ()
forall a. Ptr a -> IO ()
freeMem Ptr Int32
minor
    (Int32, Int32) -> IO (Int32, Int32)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int32
major', Int32
minor')

#if defined(ENABLE_OVERLOADING)
data GLContextGetVersionMethodInfo
instance (signature ~ (m ((Int32, Int32))), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextGetVersionMethodInfo a signature where
    overloadedMethod = gLContextGetVersion

instance O.OverloadedMethodInfo GLContextGetVersionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetVersion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextGetVersion"
        })


#endif

-- method GLContext::is_legacy
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , 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_gl_context_is_legacy" gdk_gl_context_is_legacy :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    IO CInt

-- | Whether the @GdkGLContext@ is in legacy mode or not.
-- 
-- The @GdkGLContext@ must be realized before calling this function.
-- 
-- When realizing a GL context, GDK will try to use the OpenGL 3.2 core
-- profile; this profile removes all the OpenGL API that was deprecated
-- prior to the 3.2 version of the specification. If the realization is
-- successful, this function will return 'P.False'.
-- 
-- If the underlying OpenGL implementation does not support core profiles,
-- GDK will fall back to a pre-3.2 compatibility profile, and this function
-- will return 'P.True'.
-- 
-- You can use the value returned by this function to decide which kind
-- of OpenGL API to use, or whether to do extension discovery, or what
-- kind of shader programs to load.
gLContextIsLegacy ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the GL context is in legacy mode
gLContextIsLegacy :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m Bool
gLContextIsLegacy 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 GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    CInt
result <- Ptr GLContext -> IO CInt
gdk_gl_context_is_legacy Ptr GLContext
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 GLContextIsLegacyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextIsLegacyMethodInfo a signature where
    overloadedMethod = gLContextIsLegacy

instance O.OverloadedMethodInfo GLContextIsLegacyMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextIsLegacy",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextIsLegacy"
        })


#endif

-- method GLContext::is_shared
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "other"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "the `GdkGLContext` that should be compatible with @self"
--                 , 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_gl_context_is_shared" gdk_gl_context_is_shared :: 
    Ptr GLContext ->                        -- self : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    Ptr GLContext ->                        -- other : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    IO CInt

-- | Checks if the two GL contexts can share resources.
-- 
-- When they can, the texture IDs from /@other@/ can be used in /@self@/. This
-- is particularly useful when passing @GdkGLTexture@ objects between
-- different contexts.
-- 
-- Contexts created for the same display with the same properties will
-- always be compatible, even if they are created for different surfaces.
-- For other contexts it depends on the GL backend.
-- 
-- Both contexts must be realized for this check to succeed. If either one
-- is not, this function will return 'P.False'.
-- 
-- /Since: 4.4/
gLContextIsShared ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a, IsGLContext b) =>
    a
    -- ^ /@self@/: a @GdkGLContext@
    -> b
    -- ^ /@other@/: the @GdkGLContext@ that should be compatible with /@self@/
    -> m Bool
    -- ^ __Returns:__ 'P.True' if the two GL contexts are compatible.
gLContextIsShared :: forall (m :: * -> *) a b.
(HasCallStack, MonadIO m, IsGLContext a, IsGLContext b) =>
a -> b -> m Bool
gLContextIsShared a
self b
other = 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 GLContext
self' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    Ptr GLContext
other' <- b -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr b
other
    CInt
result <- Ptr GLContext -> Ptr GLContext -> IO CInt
gdk_gl_context_is_shared Ptr GLContext
self' Ptr GLContext
other'
    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
self
    b -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr b
other
    Bool -> IO Bool
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'

#if defined(ENABLE_OVERLOADING)
data GLContextIsSharedMethodInfo
instance (signature ~ (b -> m Bool), MonadIO m, IsGLContext a, IsGLContext b) => O.OverloadedMethod GLContextIsSharedMethodInfo a signature where
    overloadedMethod = gLContextIsShared

instance O.OverloadedMethodInfo GLContextIsSharedMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextIsShared",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextIsShared"
        })


#endif

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

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

-- | Makes the /@context@/ the current one.
gLContextMakeCurrent ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m ()
gLContextMakeCurrent :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m ()
gLContextMakeCurrent a
context = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr GLContext -> IO ()
gdk_gl_context_make_current Ptr GLContext
context'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GLContextMakeCurrentMethodInfo
instance (signature ~ (m ()), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextMakeCurrentMethodInfo a signature where
    overloadedMethod = gLContextMakeCurrent

instance O.OverloadedMethodInfo GLContextMakeCurrentMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextMakeCurrent",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextMakeCurrent"
        })


#endif

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

foreign import ccall "gdk_gl_context_realize" gdk_gl_context_realize :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    Ptr (Ptr GError) ->                     -- error
    IO CInt

-- | Realizes the given @GdkGLContext@.
-- 
-- It is safe to call this function on a realized @GdkGLContext@.
gLContextRealize ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> m ()
    -- ^ /(Can throw 'Data.GI.Base.GError.GError')/
gLContextRealize :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m ()
gLContextRealize a
context = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO a
onException (do
        CInt
_ <- (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a. (Ptr (Ptr GError) -> IO a) -> IO a
propagateGError ((Ptr (Ptr GError) -> IO CInt) -> IO CInt)
-> (Ptr (Ptr GError) -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ Ptr GLContext -> Ptr (Ptr GError) -> IO CInt
gdk_gl_context_realize Ptr GLContext
context'
        a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )

#if defined(ENABLE_OVERLOADING)
data GLContextRealizeMethodInfo
instance (signature ~ (m ()), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextRealizeMethodInfo a signature where
    overloadedMethod = gLContextRealize

instance O.OverloadedMethodInfo GLContextRealizeMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextRealize",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextRealize"
        })


#endif

-- method GLContext::set_allowed_apis
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "self"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a GL context" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "apis"
--           , argType = TInterface Name { namespace = "Gdk" , name = "GLAPI" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the allowed APIs" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_gl_context_set_allowed_apis" gdk_gl_context_set_allowed_apis :: 
    Ptr GLContext ->                        -- self : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    CUInt ->                                -- apis : TInterface (Name {namespace = "Gdk", name = "GLAPI"})
    IO ()

-- | Sets the allowed APIs. When 'GI.Gdk.Objects.GLContext.gLContextRealize' is called, only the
-- allowed APIs will be tried. If you set this to 0, realizing will always fail.
-- 
-- If you set it on a realized context, the property will not have any effect.
-- It is only relevant during 'GI.Gdk.Objects.GLContext.gLContextRealize'.
-- 
-- By default, all APIs are allowed.
-- 
-- /Since: 4.6/
gLContextSetAllowedApis ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@self@/: a GL context
    -> [Gdk.Flags.GLAPI]
    -- ^ /@apis@/: the allowed APIs
    -> m ()
gLContextSetAllowedApis :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> [GLAPI] -> m ()
gLContextSetAllowedApis a
self [GLAPI]
apis = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
self' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
self
    let apis' :: CUInt
apis' = [GLAPI] -> CUInt
forall b a. (Num b, IsGFlag a) => [a] -> b
gflagsToWord [GLAPI]
apis
    Ptr GLContext -> CUInt -> IO ()
gdk_gl_context_set_allowed_apis Ptr GLContext
self' CUInt
apis'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
self
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GLContextSetAllowedApisMethodInfo
instance (signature ~ ([Gdk.Flags.GLAPI] -> m ()), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextSetAllowedApisMethodInfo a signature where
    overloadedMethod = gLContextSetAllowedApis

instance O.OverloadedMethodInfo GLContextSetAllowedApisMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextSetAllowedApis",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextSetAllowedApis"
        })


#endif

-- method GLContext::set_debug_enabled
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "enabled"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "whether to enable debugging in the context"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_gl_context_set_debug_enabled" gdk_gl_context_set_debug_enabled :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    CInt ->                                 -- enabled : TBasicType TBoolean
    IO ()

-- | Sets whether the @GdkGLContext@ should perform extra validations and
-- runtime checking.
-- 
-- This is useful during development, but has additional overhead.
-- 
-- The @GdkGLContext@ must not be realized or made current prior to
-- calling this function.
gLContextSetDebugEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> Bool
    -- ^ /@enabled@/: whether to enable debugging in the context
    -> m ()
gLContextSetDebugEnabled :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> Bool -> m ()
gLContextSetDebugEnabled a
context Bool
enabled = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    let enabled' :: CInt
enabled' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
enabled
    Ptr GLContext -> CInt -> IO ()
gdk_gl_context_set_debug_enabled Ptr GLContext
context' CInt
enabled'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GLContextSetDebugEnabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextSetDebugEnabledMethodInfo a signature where
    overloadedMethod = gLContextSetDebugEnabled

instance O.OverloadedMethodInfo GLContextSetDebugEnabledMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextSetDebugEnabled",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextSetDebugEnabled"
        })


#endif

-- method GLContext::set_forward_compatible
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "compatible"
--           , argType = TBasicType TBoolean
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just "whether the context should be forward-compatible"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_gl_context_set_forward_compatible" gdk_gl_context_set_forward_compatible :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    CInt ->                                 -- compatible : TBasicType TBoolean
    IO ()

-- | Sets whether the @GdkGLContext@ should be forward-compatible.
-- 
-- Forward-compatible contexts must not support OpenGL functionality that
-- has been marked as deprecated in the requested version; non-forward
-- compatible contexts, on the other hand, must support both deprecated and
-- non deprecated functionality.
-- 
-- The @GdkGLContext@ must not be realized or made current prior to calling
-- this function.
gLContextSetForwardCompatible ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> Bool
    -- ^ /@compatible@/: whether the context should be forward-compatible
    -> m ()
gLContextSetForwardCompatible :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> Bool -> m ()
gLContextSetForwardCompatible a
context Bool
compatible = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    let compatible' :: CInt
compatible' = (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
P.fromIntegral (Int -> CInt) -> (Bool -> Int) -> Bool -> CInt
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
P.fromEnum) Bool
compatible
    Ptr GLContext -> CInt -> IO ()
gdk_gl_context_set_forward_compatible Ptr GLContext
context' CInt
compatible'
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GLContextSetForwardCompatibleMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextSetForwardCompatibleMethodInfo a signature where
    overloadedMethod = gLContextSetForwardCompatible

instance O.OverloadedMethodInfo GLContextSetForwardCompatibleMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextSetForwardCompatible",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextSetForwardCompatible"
        })


#endif

-- method GLContext::set_required_version
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "major"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the major version to request"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "minor"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "the minor version to request"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_gl_context_set_required_version" gdk_gl_context_set_required_version :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    Int32 ->                                -- major : TBasicType TInt
    Int32 ->                                -- minor : TBasicType TInt
    IO ()

-- | Sets the major and minor version of OpenGL to request.
-- 
-- Setting /@major@/ and /@minor@/ to zero will use the default values.
-- 
-- Setting /@major@/ and /@minor@/ lower than the minimum versions required
-- by GTK will result in the context choosing the minimum version.
-- 
-- The /@context@/ must not be realized or made current prior to calling
-- this function.
gLContextSetRequiredVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> Int32
    -- ^ /@major@/: the major version to request
    -> Int32
    -- ^ /@minor@/: the minor version to request
    -> m ()
gLContextSetRequiredVersion :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> Int32 -> Int32 -> m ()
gLContextSetRequiredVersion a
context Int32
major Int32
minor = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr GLContext -> Int32 -> Int32 -> IO ()
gdk_gl_context_set_required_version Ptr GLContext
context' Int32
major Int32
minor
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GLContextSetRequiredVersionMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextSetRequiredVersionMethodInfo a signature where
    overloadedMethod = gLContextSetRequiredVersion

instance O.OverloadedMethodInfo GLContextSetRequiredVersionMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextSetRequiredVersion",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextSetRequiredVersion"
        })


#endif

-- method GLContext::set_use_es
-- method type : OrdinaryMethod
-- Args: [ Arg
--           { argCName = "context"
--           , argType =
--               TInterface Name { namespace = "Gdk" , name = "GLContext" }
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText = Just "a `GdkGLContext`" , sinceVersion = Nothing }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       , Arg
--           { argCName = "use_es"
--           , argType = TBasicType TInt
--           , direction = DirectionIn
--           , mayBeNull = False
--           , argDoc =
--               Documentation
--                 { rawDocText =
--                     Just
--                       "whether the context should use OpenGL ES instead of OpenGL,\n  or -1 to allow auto-detection"
--                 , sinceVersion = Nothing
--                 }
--           , argScope = ScopeTypeInvalid
--           , argClosure = -1
--           , argDestroy = -1
--           , argCallerAllocates = False
--           , transfer = TransferNothing
--           }
--       ]
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_gl_context_set_use_es" gdk_gl_context_set_use_es :: 
    Ptr GLContext ->                        -- context : TInterface (Name {namespace = "Gdk", name = "GLContext"})
    Int32 ->                                -- use_es : TBasicType TInt
    IO ()

-- | Requests that GDK create an OpenGL ES context instead of an OpenGL one.
-- 
-- Not all platforms support OpenGL ES.
-- 
-- The /@context@/ must not have been realized.
-- 
-- By default, GDK will attempt to automatically detect whether the
-- underlying GL implementation is OpenGL or OpenGL ES once the /@context@/
-- is realized.
-- 
-- You should check the return value of 'GI.Gdk.Objects.GLContext.gLContextGetUseEs'
-- after calling 'GI.Gdk.Objects.GLContext.gLContextRealize' to decide whether to use
-- the OpenGL or OpenGL ES API, extensions, or shaders.
gLContextSetUseEs ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    -- ^ /@context@/: a @GdkGLContext@
    -> Int32
    -- ^ /@useEs@/: whether the context should use OpenGL ES instead of OpenGL,
    --   or -1 to allow auto-detection
    -> m ()
gLContextSetUseEs :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> Int32 -> m ()
gLContextSetUseEs a
context Int32
useEs = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
context' <- a -> IO (Ptr GLContext)
forall a b. (HasCallStack, ManagedPtrNewtype a) => a -> IO (Ptr b)
unsafeManagedPtrCastPtr a
context
    Ptr GLContext -> Int32 -> IO ()
gdk_gl_context_set_use_es Ptr GLContext
context' Int32
useEs
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
data GLContextSetUseEsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGLContext a) => O.OverloadedMethod GLContextSetUseEsMethodInfo a signature where
    overloadedMethod = gLContextSetUseEs

instance O.OverloadedMethodInfo GLContextSetUseEsMethodInfo a where
    overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
        O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextSetUseEs",
        O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-4.0.7/docs/GI-Gdk-Objects-GLContext.html#v:gLContextSetUseEs"
        })


#endif

-- method GLContext::clear_current
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Nothing
-- throws : False
-- Skip return : False

foreign import ccall "gdk_gl_context_clear_current" gdk_gl_context_clear_current :: 
    IO ()

-- | Clears the current @GdkGLContext@.
-- 
-- Any OpenGL call after this function returns will be ignored
-- until 'GI.Gdk.Objects.GLContext.gLContextMakeCurrent' is called.
gLContextClearCurrent ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ()
gLContextClearCurrent :: forall (m :: * -> *). (HasCallStack, MonadIO m) => m ()
gLContextClearCurrent  = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    IO ()
gdk_gl_context_clear_current
    () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()

#if defined(ENABLE_OVERLOADING)
#endif

-- method GLContext::get_current
-- method type : MemberFunction
-- Args: []
-- Lengths: []
-- returnType: Just (TInterface Name { namespace = "Gdk" , name = "GLContext" })
-- throws : False
-- Skip return : False

foreign import ccall "gdk_gl_context_get_current" gdk_gl_context_get_current :: 
    IO (Ptr GLContext)

-- | Retrieves the current @GdkGLContext@.
gLContextGetCurrent ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m (Maybe GLContext)
    -- ^ __Returns:__ the current @GdkGLContext@
gLContextGetCurrent :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
m (Maybe GLContext)
gLContextGetCurrent  = IO (Maybe GLContext) -> m (Maybe GLContext)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe GLContext) -> m (Maybe GLContext))
-> IO (Maybe GLContext) -> m (Maybe GLContext)
forall a b. (a -> b) -> a -> b
$ do
    Ptr GLContext
result <- IO (Ptr GLContext)
gdk_gl_context_get_current
    Maybe GLContext
maybeResult <- Ptr GLContext
-> (Ptr GLContext -> IO GLContext) -> IO (Maybe GLContext)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr GLContext
result ((Ptr GLContext -> IO GLContext) -> IO (Maybe GLContext))
-> (Ptr GLContext -> IO GLContext) -> IO (Maybe GLContext)
forall a b. (a -> b) -> a -> b
$ \Ptr GLContext
result' -> do
        GLContext
result'' <- ((ManagedPtr GLContext -> GLContext)
-> Ptr GLContext -> IO GLContext
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr GLContext -> GLContext
GLContext) Ptr GLContext
result'
        GLContext -> IO GLContext
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return GLContext
result''
    Maybe GLContext -> IO (Maybe GLContext)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GLContext
maybeResult

#if defined(ENABLE_OVERLOADING)
#endif