{-# LANGUAGE TypeApplications #-}
#if (MIN_VERSION_haskell_gi_overloading(1,0,0) && !defined(__HADDOCK_VERSION__))
#define ENABLE_OVERLOADING
#endif
module GI.Gdk.Objects.GLContext
    ( 
    GLContext(..)                           ,
    IsGLContext                             ,
    toGLContext                             ,
    noGLContext                             ,
 
#if defined(ENABLE_OVERLOADING)
    ResolveGLContextMethod                  ,
#endif
    gLContextClearCurrent                   ,
    gLContextGetCurrent                     ,
#if defined(ENABLE_OVERLOADING)
    GLContextGetDebugEnabledMethodInfo      ,
#endif
    gLContextGetDebugEnabled                ,
#if defined(ENABLE_OVERLOADING)
    GLContextGetDisplayMethodInfo           ,
#endif
    gLContextGetDisplay                     ,
#if defined(ENABLE_OVERLOADING)
    GLContextGetForwardCompatibleMethodInfo ,
#endif
    gLContextGetForwardCompatible           ,
#if defined(ENABLE_OVERLOADING)
    GLContextGetRequiredVersionMethodInfo   ,
#endif
    gLContextGetRequiredVersion             ,
#if defined(ENABLE_OVERLOADING)
    GLContextGetSharedContextMethodInfo     ,
#endif
    gLContextGetSharedContext               ,
#if defined(ENABLE_OVERLOADING)
    GLContextGetUseEsMethodInfo             ,
#endif
    gLContextGetUseEs                       ,
#if defined(ENABLE_OVERLOADING)
    GLContextGetVersionMethodInfo           ,
#endif
    gLContextGetVersion                     ,
#if defined(ENABLE_OVERLOADING)
    GLContextGetWindowMethodInfo            ,
#endif
    gLContextGetWindow                      ,
#if defined(ENABLE_OVERLOADING)
    GLContextIsLegacyMethodInfo             ,
#endif
    gLContextIsLegacy                       ,
#if defined(ENABLE_OVERLOADING)
    GLContextMakeCurrentMethodInfo          ,
#endif
    gLContextMakeCurrent                    ,
#if defined(ENABLE_OVERLOADING)
    GLContextRealizeMethodInfo              ,
#endif
    gLContextRealize                        ,
#if defined(ENABLE_OVERLOADING)
    GLContextSetDebugEnabledMethodInfo      ,
#endif
    gLContextSetDebugEnabled                ,
#if defined(ENABLE_OVERLOADING)
    GLContextSetForwardCompatibleMethodInfo ,
#endif
    gLContextSetForwardCompatible           ,
#if defined(ENABLE_OVERLOADING)
    GLContextSetRequiredVersionMethodInfo   ,
#endif
    gLContextSetRequiredVersion             ,
#if defined(ENABLE_OVERLOADING)
    GLContextSetUseEsMethodInfo             ,
#endif
    gLContextSetUseEs                       ,
 
#if defined(ENABLE_OVERLOADING)
    GLContextDisplayPropertyInfo            ,
#endif
    constructGLContextDisplay               ,
#if defined(ENABLE_OVERLOADING)
    gLContextDisplay                        ,
#endif
    getGLContextDisplay                     ,
#if defined(ENABLE_OVERLOADING)
    GLContextSharedContextPropertyInfo      ,
#endif
    constructGLContextSharedContext         ,
#if defined(ENABLE_OVERLOADING)
    gLContextSharedContext                  ,
#endif
    getGLContextSharedContext               ,
#if defined(ENABLE_OVERLOADING)
    GLContextWindowPropertyInfo             ,
#endif
    constructGLContextWindow                ,
#if defined(ENABLE_OVERLOADING)
    gLContextWindow                         ,
#endif
    getGLContextWindow                      ,
    ) where
import Data.GI.Base.ShortPrelude
import qualified Data.GI.Base.ShortPrelude as SP
import qualified Data.GI.Base.Overloading as O
import qualified Prelude as P
import qualified Data.GI.Base.Attributes as GI.Attributes
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GI.GObject.Objects.Object as GObject.Object
import {-# SOURCE #-} qualified GI.Gdk.Objects.Display as Gdk.Display
import {-# SOURCE #-} qualified GI.Gdk.Objects.Window as Gdk.Window
newtype GLContext = GLContext (ManagedPtr GLContext)
    deriving (GLContext -> GLContext -> Bool
(GLContext -> GLContext -> Bool)
-> (GLContext -> GLContext -> Bool) -> Eq GLContext
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GLContext -> GLContext -> Bool
$c/= :: GLContext -> GLContext -> Bool
== :: GLContext -> GLContext -> Bool
$c== :: GLContext -> GLContext -> Bool
Eq)
foreign import ccall "gdk_gl_context_get_type"
    c_gdk_gl_context_get_type :: IO GType
instance GObject GLContext where
    gobjectType :: IO GType
gobjectType = IO GType
c_gdk_gl_context_get_type
    
instance B.GValue.IsGValue GLContext where
    toGValue :: GLContext -> IO GValue
toGValue o :: GLContext
o = do
        GType
gtype <- IO GType
c_gdk_gl_context_get_type
        GLContext -> (Ptr GLContext -> IO GValue) -> IO GValue
forall a c.
(HasCallStack, ManagedPtrNewtype a) =>
a -> (Ptr a -> IO c) -> IO c
B.ManagedPtr.withManagedPtr GLContext
o (GType
-> (GValue -> Ptr GLContext -> IO ()) -> Ptr GLContext -> IO GValue
forall a. GType -> (GValue -> a -> IO ()) -> a -> IO GValue
B.GValue.buildGValue GType
gtype GValue -> Ptr GLContext -> IO ()
forall a. GObject a => GValue -> Ptr a -> IO ()
B.GValue.set_object)
        
    fromGValue :: GValue -> IO GLContext
fromGValue gv :: GValue
gv = do
        Ptr GLContext
ptr <- GValue -> IO (Ptr GLContext)
forall b. GObject b => GValue -> IO (Ptr b)
B.GValue.get_object GValue
gv :: IO (Ptr GLContext)
        (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
        
    
class (GObject o, O.IsDescendantOf GLContext o) => IsGLContext o
instance (GObject o, O.IsDescendantOf GLContext o) => IsGLContext o
instance O.HasParentTypes GLContext
type instance O.ParentTypes GLContext = '[GObject.Object.Object]
toGLContext :: (MonadIO m, IsGLContext o) => o -> m GLContext
toGLContext :: o -> m GLContext
toGLContext = IO GLContext -> m GLContext
forall (m :: * -> *) a. MonadIO m => IO a -> m a
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, GObject o, GObject o') =>
(ManagedPtr o' -> o') -> o -> IO o'
unsafeCastTo ManagedPtr GLContext -> GLContext
GLContext
noGLContext :: Maybe GLContext
noGLContext :: Maybe GLContext
noGLContext = Maybe GLContext
forall a. Maybe a
Nothing
#if defined(ENABLE_OVERLOADING)
type family ResolveGLContextMethod (t :: Symbol) (o :: *) :: * where
    ResolveGLContextMethod "bindProperty" o = GObject.Object.ObjectBindPropertyMethodInfo
    ResolveGLContextMethod "bindPropertyFull" o = GObject.Object.ObjectBindPropertyFullMethodInfo
    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 "isLegacy" o = GLContextIsLegacyMethodInfo
    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 "getData" o = GObject.Object.ObjectGetDataMethodInfo
    ResolveGLContextMethod "getDebugEnabled" o = GLContextGetDebugEnabledMethodInfo
    ResolveGLContextMethod "getDisplay" o = GLContextGetDisplayMethodInfo
    ResolveGLContextMethod "getForwardCompatible" o = GLContextGetForwardCompatibleMethodInfo
    ResolveGLContextMethod "getProperty" o = GObject.Object.ObjectGetPropertyMethodInfo
    ResolveGLContextMethod "getQdata" o = GObject.Object.ObjectGetQdataMethodInfo
    ResolveGLContextMethod "getRequiredVersion" o = GLContextGetRequiredVersionMethodInfo
    ResolveGLContextMethod "getSharedContext" o = GLContextGetSharedContextMethodInfo
    ResolveGLContextMethod "getUseEs" o = GLContextGetUseEsMethodInfo
    ResolveGLContextMethod "getVersion" o = GLContextGetVersionMethodInfo
    ResolveGLContextMethod "getWindow" o = GLContextGetWindowMethodInfo
    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.MethodInfo 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
#endif
   
   
   
getGLContextDisplay :: (MonadIO m, IsGLContext o) => o -> m (Maybe Gdk.Display.Display)
getGLContextDisplay :: o -> m (Maybe Display)
getGLContextDisplay obj :: o
obj = IO (Maybe Display) -> m (Maybe Display)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Display -> Display) -> IO (Maybe Display)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "display" ManagedPtr Display -> Display
Gdk.Display.Display
constructGLContextDisplay :: (IsGLContext o, Gdk.Display.IsDisplay a) => a -> IO (GValueConstruct o)
constructGLContextDisplay :: a -> IO (GValueConstruct o)
constructGLContextDisplay val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "display" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
#if defined(ENABLE_OVERLOADING)
data GLContextDisplayPropertyInfo
instance AttrInfo GLContextDisplayPropertyInfo where
    type AttrAllowedOps GLContextDisplayPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint GLContextDisplayPropertyInfo = IsGLContext
    type AttrSetTypeConstraint GLContextDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferTypeConstraint GLContextDisplayPropertyInfo = Gdk.Display.IsDisplay
    type AttrTransferType GLContextDisplayPropertyInfo = Gdk.Display.Display
    type AttrGetType GLContextDisplayPropertyInfo = (Maybe Gdk.Display.Display)
    type AttrLabel GLContextDisplayPropertyInfo = "display"
    type AttrOrigin GLContextDisplayPropertyInfo = GLContext
    attrGet = getGLContextDisplay
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gdk.Display.Display v
    attrConstruct = constructGLContextDisplay
    attrClear = undefined
#endif
   
   
   
getGLContextSharedContext :: (MonadIO m, IsGLContext o) => o -> m (Maybe GLContext)
getGLContextSharedContext :: o -> m (Maybe GLContext)
getGLContextSharedContext obj :: o
obj = IO (Maybe GLContext) -> m (Maybe GLContext)
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
$ 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 "shared-context" ManagedPtr GLContext -> GLContext
GLContext
constructGLContextSharedContext :: (IsGLContext o, IsGLContext a) => a -> IO (GValueConstruct o)
constructGLContextSharedContext :: a -> IO (GValueConstruct o)
constructGLContextSharedContext val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "shared-context" (a -> Maybe a
forall a. a -> Maybe a
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
#endif
   
   
   
getGLContextWindow :: (MonadIO m, IsGLContext o) => o -> m (Maybe Gdk.Window.Window)
getGLContextWindow :: o -> m (Maybe Window)
getGLContextWindow obj :: o
obj = IO (Maybe Window) -> m (Maybe Window)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
forall a b. (a -> b) -> a -> b
$ o -> String -> (ManagedPtr Window -> Window) -> IO (Maybe Window)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj "window" ManagedPtr Window -> Window
Gdk.Window.Window
constructGLContextWindow :: (IsGLContext o, Gdk.Window.IsWindow a) => a -> IO (GValueConstruct o)
constructGLContextWindow :: a -> IO (GValueConstruct o)
constructGLContextWindow val :: a
val = String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject "window" (a -> Maybe a
forall a. a -> Maybe a
Just a
val)
#if defined(ENABLE_OVERLOADING)
data GLContextWindowPropertyInfo
instance AttrInfo GLContextWindowPropertyInfo where
    type AttrAllowedOps GLContextWindowPropertyInfo = '[ 'AttrConstruct, 'AttrGet, 'AttrClear]
    type AttrBaseTypeConstraint GLContextWindowPropertyInfo = IsGLContext
    type AttrSetTypeConstraint GLContextWindowPropertyInfo = Gdk.Window.IsWindow
    type AttrTransferTypeConstraint GLContextWindowPropertyInfo = Gdk.Window.IsWindow
    type AttrTransferType GLContextWindowPropertyInfo = Gdk.Window.Window
    type AttrGetType GLContextWindowPropertyInfo = (Maybe Gdk.Window.Window)
    type AttrLabel GLContextWindowPropertyInfo = "window"
    type AttrOrigin GLContextWindowPropertyInfo = GLContext
    attrGet = getGLContextWindow
    attrSet = undefined
    attrTransfer _ v = do
        unsafeCastTo Gdk.Window.Window v
    attrConstruct = constructGLContextWindow
    attrClear = undefined
#endif
#if defined(ENABLE_OVERLOADING)
instance O.HasAttributeList GLContext
type instance O.AttributeList GLContext = GLContextAttributeList
type GLContextAttributeList = ('[ '("display", GLContextDisplayPropertyInfo), '("sharedContext", GLContextSharedContextPropertyInfo), '("window", GLContextWindowPropertyInfo)] :: [(Symbol, *)])
#endif
#if defined(ENABLE_OVERLOADING)
gLContextDisplay :: AttrLabelProxy "display"
gLContextDisplay = AttrLabelProxy
gLContextSharedContext :: AttrLabelProxy "sharedContext"
gLContextSharedContext = AttrLabelProxy
gLContextWindow :: AttrLabelProxy "window"
gLContextWindow = AttrLabelProxy
#endif
#if defined(ENABLE_OVERLOADING)
type instance O.SignalList GLContext = GLContextSignalList
type GLContextSignalList = ('[ '("notify", GObject.Object.ObjectNotifySignalInfo)] :: [(Symbol, *)])
#endif
foreign import ccall "gdk_gl_context_get_debug_enabled" gdk_gl_context_get_debug_enabled :: 
    Ptr GLContext ->                        
    IO CInt
gLContextGetDebugEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m Bool
    
gLContextGetDebugEnabled :: a -> m Bool
gLContextGetDebugEnabled context :: a
context = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data GLContextGetDebugEnabledMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGLContext a) => O.MethodInfo GLContextGetDebugEnabledMethodInfo a signature where
    overloadedMethod = gLContextGetDebugEnabled
#endif
foreign import ccall "gdk_gl_context_get_display" gdk_gl_context_get_display :: 
    Ptr GLContext ->                        
    IO (Ptr Gdk.Display.Display)
gLContextGetDisplay ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m (Maybe Gdk.Display.Display)
    
gLContextGetDisplay :: a -> m (Maybe Display)
gLContextGetDisplay context :: a
context = IO (Maybe Display) -> m (Maybe Display)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
$ \result' :: Ptr Display
result' -> do
        Display
result'' <- ((ManagedPtr Display -> Display) -> Ptr Display -> IO Display
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Display -> Display
Gdk.Display.Display) Ptr Display
result'
        Display -> IO Display
forall (m :: * -> *) a. Monad m => a -> m a
return Display
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Maybe Display -> IO (Maybe Display)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Display
maybeResult
#if defined(ENABLE_OVERLOADING)
data GLContextGetDisplayMethodInfo
instance (signature ~ (m (Maybe Gdk.Display.Display)), MonadIO m, IsGLContext a) => O.MethodInfo GLContextGetDisplayMethodInfo a signature where
    overloadedMethod = gLContextGetDisplay
#endif
foreign import ccall "gdk_gl_context_get_forward_compatible" gdk_gl_context_get_forward_compatible :: 
    Ptr GLContext ->                        
    IO CInt
gLContextGetForwardCompatible ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m Bool
    
gLContextGetForwardCompatible :: a -> m Bool
gLContextGetForwardCompatible context :: a
context = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data GLContextGetForwardCompatibleMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGLContext a) => O.MethodInfo GLContextGetForwardCompatibleMethodInfo a signature where
    overloadedMethod = gLContextGetForwardCompatible
#endif
foreign import ccall "gdk_gl_context_get_required_version" gdk_gl_context_get_required_version :: 
    Ptr GLContext ->                        
    Ptr Int32 ->                            
    Ptr Int32 ->                            
    IO ()
gLContextGetRequiredVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m ((Int32, Int32))
gLContextGetRequiredVersion :: a -> m (Int32, Int32)
gLContextGetRequiredVersion context :: a
context = IO (Int32, Int32) -> m (Int32, Int32)
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 (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.MethodInfo GLContextGetRequiredVersionMethodInfo a signature where
    overloadedMethod = gLContextGetRequiredVersion
#endif
foreign import ccall "gdk_gl_context_get_shared_context" gdk_gl_context_get_shared_context :: 
    Ptr GLContext ->                        
    IO (Ptr GLContext)
gLContextGetSharedContext ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m (Maybe GLContext)
    
gLContextGetSharedContext :: a -> m (Maybe GLContext)
gLContextGetSharedContext context :: a
context = IO (Maybe GLContext) -> m (Maybe GLContext)
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
$ \result' :: 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 (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 (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.MethodInfo GLContextGetSharedContextMethodInfo a signature where
    overloadedMethod = gLContextGetSharedContext
#endif
foreign import ccall "gdk_gl_context_get_use_es" gdk_gl_context_get_use_es :: 
    Ptr GLContext ->                        
    IO CInt
gLContextGetUseEs ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m Bool
    
gLContextGetUseEs :: a -> m Bool
gLContextGetUseEs context :: a
context = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data GLContextGetUseEsMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGLContext a) => O.MethodInfo GLContextGetUseEsMethodInfo a signature where
    overloadedMethod = gLContextGetUseEs
#endif
foreign import ccall "gdk_gl_context_get_version" gdk_gl_context_get_version :: 
    Ptr GLContext ->                        
    Ptr Int32 ->                            
    Ptr Int32 ->                            
    IO ()
gLContextGetVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m ((Int32, Int32))
gLContextGetVersion :: a -> m (Int32, Int32)
gLContextGetVersion context :: a
context = IO (Int32, Int32) -> m (Int32, Int32)
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 (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.MethodInfo GLContextGetVersionMethodInfo a signature where
    overloadedMethod = gLContextGetVersion
#endif
foreign import ccall "gdk_gl_context_get_window" gdk_gl_context_get_window :: 
    Ptr GLContext ->                        
    IO (Ptr Gdk.Window.Window)
gLContextGetWindow ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m (Maybe Gdk.Window.Window)
    
gLContextGetWindow :: a -> m (Maybe Window)
gLContextGetWindow context :: a
context = IO (Maybe Window) -> m (Maybe Window)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe Window) -> m (Maybe Window))
-> IO (Maybe Window) -> m (Maybe Window)
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 Window
result <- Ptr GLContext -> IO (Ptr Window)
gdk_gl_context_get_window Ptr GLContext
context'
    Maybe Window
maybeResult <- Ptr Window -> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. Ptr a -> (Ptr a -> IO b) -> IO (Maybe b)
convertIfNonNull Ptr Window
result ((Ptr Window -> IO Window) -> IO (Maybe Window))
-> (Ptr Window -> IO Window) -> IO (Maybe Window)
forall a b. (a -> b) -> a -> b
$ \result' :: Ptr Window
result' -> do
        Window
result'' <- ((ManagedPtr Window -> Window) -> Ptr Window -> IO Window
forall a b.
(HasCallStack, GObject a, GObject b) =>
(ManagedPtr a -> a) -> Ptr b -> IO a
newObject ManagedPtr Window -> Window
Gdk.Window.Window) Ptr Window
result'
        Window -> IO Window
forall (m :: * -> *) a. Monad m => a -> m a
return Window
result''
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Maybe Window -> IO (Maybe Window)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Window
maybeResult
#if defined(ENABLE_OVERLOADING)
data GLContextGetWindowMethodInfo
instance (signature ~ (m (Maybe Gdk.Window.Window)), MonadIO m, IsGLContext a) => O.MethodInfo GLContextGetWindowMethodInfo a signature where
    overloadedMethod = gLContextGetWindow
#endif
foreign import ccall "gdk_gl_context_is_legacy" gdk_gl_context_is_legacy :: 
    Ptr GLContext ->                        
    IO CInt
gLContextIsLegacy ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m Bool
    
gLContextIsLegacy :: a -> m Bool
gLContextIsLegacy context :: a
context = IO Bool -> m Bool
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
/= 0) CInt
result
    a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
    Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data GLContextIsLegacyMethodInfo
instance (signature ~ (m Bool), MonadIO m, IsGLContext a) => O.MethodInfo GLContextIsLegacyMethodInfo a signature where
    overloadedMethod = gLContextIsLegacy
#endif
foreign import ccall "gdk_gl_context_make_current" gdk_gl_context_make_current :: 
    Ptr GLContext ->                        
    IO ()
gLContextMakeCurrent ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m ()
gLContextMakeCurrent :: a -> m ()
gLContextMakeCurrent context :: a
context = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GLContextMakeCurrentMethodInfo
instance (signature ~ (m ()), MonadIO m, IsGLContext a) => O.MethodInfo GLContextMakeCurrentMethodInfo a signature where
    overloadedMethod = gLContextMakeCurrent
#endif
foreign import ccall "gdk_gl_context_realize" gdk_gl_context_realize :: 
    Ptr GLContext ->                        
    Ptr (Ptr GError) ->                     
    IO CInt
gLContextRealize ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> m ()
    
gLContextRealize :: a -> m ()
gLContextRealize context :: a
context = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()
     ) (do
        () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
     )
#if defined(ENABLE_OVERLOADING)
data GLContextRealizeMethodInfo
instance (signature ~ (m ()), MonadIO m, IsGLContext a) => O.MethodInfo GLContextRealizeMethodInfo a signature where
    overloadedMethod = gLContextRealize
#endif
foreign import ccall "gdk_gl_context_set_debug_enabled" gdk_gl_context_set_debug_enabled :: 
    Ptr GLContext ->                        
    CInt ->                                 
    IO ()
gLContextSetDebugEnabled ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> Bool
    
    -> m ()
gLContextSetDebugEnabled :: a -> Bool -> m ()
gLContextSetDebugEnabled context :: a
context enabled :: Bool
enabled = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
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
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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GLContextSetDebugEnabledMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGLContext a) => O.MethodInfo GLContextSetDebugEnabledMethodInfo a signature where
    overloadedMethod = gLContextSetDebugEnabled
#endif
foreign import ccall "gdk_gl_context_set_forward_compatible" gdk_gl_context_set_forward_compatible :: 
    Ptr GLContext ->                        
    CInt ->                                 
    IO ()
gLContextSetForwardCompatible ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> Bool
    
    -> m ()
gLContextSetForwardCompatible :: a -> Bool -> m ()
gLContextSetForwardCompatible context :: a
context compatible :: Bool
compatible = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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
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
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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GLContextSetForwardCompatibleMethodInfo
instance (signature ~ (Bool -> m ()), MonadIO m, IsGLContext a) => O.MethodInfo GLContextSetForwardCompatibleMethodInfo a signature where
    overloadedMethod = gLContextSetForwardCompatible
#endif
foreign import ccall "gdk_gl_context_set_required_version" gdk_gl_context_set_required_version :: 
    Ptr GLContext ->                        
    Int32 ->                                
    Int32 ->                                
    IO ()
gLContextSetRequiredVersion ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> Int32
    
    -> Int32
    
    -> m ()
gLContextSetRequiredVersion :: a -> Int32 -> Int32 -> m ()
gLContextSetRequiredVersion context :: a
context major :: Int32
major minor :: Int32
minor = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GLContextSetRequiredVersionMethodInfo
instance (signature ~ (Int32 -> Int32 -> m ()), MonadIO m, IsGLContext a) => O.MethodInfo GLContextSetRequiredVersionMethodInfo a signature where
    overloadedMethod = gLContextSetRequiredVersion
#endif
foreign import ccall "gdk_gl_context_set_use_es" gdk_gl_context_set_use_es :: 
    Ptr GLContext ->                        
    Int32 ->                                
    IO ()
gLContextSetUseEs ::
    (B.CallStack.HasCallStack, MonadIO m, IsGLContext a) =>
    a
    
    -> Int32
    
    
    -> m ()
gLContextSetUseEs :: a -> Int32 -> m ()
gLContextSetUseEs context :: a
context useEs :: Int32
useEs = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ do
    Ptr 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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
data GLContextSetUseEsMethodInfo
instance (signature ~ (Int32 -> m ()), MonadIO m, IsGLContext a) => O.MethodInfo GLContextSetUseEsMethodInfo a signature where
    overloadedMethod = gLContextSetUseEs
#endif
foreign import ccall "gdk_gl_context_clear_current" gdk_gl_context_clear_current :: 
    IO ()
gLContextClearCurrent ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m ()
gLContextClearCurrent :: m ()
gLContextClearCurrent  = IO () -> m ()
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 (m :: * -> *) a. Monad m => a -> m a
return ()
#if defined(ENABLE_OVERLOADING)
#endif
foreign import ccall "gdk_gl_context_get_current" gdk_gl_context_get_current :: 
    IO (Ptr GLContext)
gLContextGetCurrent ::
    (B.CallStack.HasCallStack, MonadIO m) =>
    m (Maybe GLContext)
    
gLContextGetCurrent :: m (Maybe GLContext)
gLContextGetCurrent  = IO (Maybe GLContext) -> m (Maybe GLContext)
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
$ \result' :: 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 (m :: * -> *) a. Monad m => a -> m a
return GLContext
result''
    Maybe GLContext -> IO (Maybe GLContext)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe GLContext
maybeResult
#if defined(ENABLE_OVERLOADING)
#endif