{-# 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 ,
#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.BasicTypes as B.Types
import qualified Data.GI.Base.ManagedPtr as B.ManagedPtr
import qualified Data.GI.Base.GArray as B.GArray
import qualified Data.GI.Base.GClosure as B.GClosure
import qualified Data.GI.Base.GError as B.GError
import qualified Data.GI.Base.GVariant as B.GVariant
import qualified Data.GI.Base.GValue as B.GValue
import qualified Data.GI.Base.GParamSpec as B.GParamSpec
import qualified Data.GI.Base.CallStack as B.CallStack
import qualified Data.GI.Base.Properties as B.Properties
import qualified Data.GI.Base.Signals as B.Signals
import qualified Control.Monad.IO.Class as MIO
import qualified Data.Coerce as Coerce
import qualified Data.Text as T
import qualified Data.ByteString.Char8 as B
import qualified Data.Map as Map
import qualified Foreign.Ptr as FP
import qualified GHC.OverloadedLabels as OL
import qualified GHC.Records as R
import qualified GI.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 (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
/= :: GLContext -> GLContext -> Bool
$c/= :: GLContext -> GLContext -> Bool
== :: GLContext -> GLContext -> Bool
$c== :: 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
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 = '[GObject.Object.Object]
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 (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
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 (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 :: *) :: * 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.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
getGLContextDisplay :: (MonadIO m, IsGLContext o) => o -> m (Maybe Gdk.Display.Display)
getGLContextDisplay :: forall (m :: * -> *) o.
(MonadIO m, IsGLContext o) =>
o -> m (Maybe Display)
getGLContextDisplay o
obj = IO (Maybe Display) -> m (Maybe Display)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (Maybe Display) -> m (Maybe Display))
-> IO (Maybe Display) -> m (Maybe Display)
forall a b. (a -> b) -> a -> b
$ o
-> String -> (ManagedPtr Display -> Display) -> IO (Maybe Display)
forall a b.
(GObject a, GObject b) =>
a -> String -> (ManagedPtr b -> b) -> IO (Maybe b)
B.Properties.getObjectPropertyObject o
obj String
"display" ManagedPtr Display -> Display
Gdk.Display.Display
constructGLContextDisplay :: (IsGLContext o, MIO.MonadIO m, Gdk.Display.IsDisplay a) => a -> m (GValueConstruct o)
constructGLContextDisplay :: forall o (m :: * -> *) a.
(IsGLContext o, MonadIO m, IsDisplay a) =>
a -> m (GValueConstruct o)
constructGLContextDisplay a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"display" (a -> Maybe a
forall a. a -> Maybe a
P.Just a
val)
#if defined(ENABLE_OVERLOADING)
data 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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.display"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-GLContext.html#g:attr:display"
})
#endif
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 (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
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 (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#g:attr:sharedContext"
})
#endif
getGLContextWindow :: (MonadIO m, IsGLContext o) => o -> m (Maybe Gdk.Window.Window)
getGLContextWindow :: forall (m :: * -> *) o.
(MonadIO m, IsGLContext o) =>
o -> m (Maybe Window)
getGLContextWindow o
obj = IO (Maybe Window) -> m (Maybe Window)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.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 String
"window" ManagedPtr Window -> Window
Gdk.Window.Window
constructGLContextWindow :: (IsGLContext o, MIO.MonadIO m, Gdk.Window.IsWindow a) => a -> m (GValueConstruct o)
constructGLContextWindow :: forall o (m :: * -> *) a.
(IsGLContext o, MonadIO m, IsWindow a) =>
a -> m (GValueConstruct o)
constructGLContextWindow a
val = IO (GValueConstruct o) -> m (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> m (GValueConstruct o))
-> IO (GValueConstruct o) -> m (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ do
IO (GValueConstruct o) -> IO (GValueConstruct o)
forall (m :: * -> *) a. MonadIO m => IO a -> m a
MIO.liftIO (IO (GValueConstruct o) -> IO (GValueConstruct o))
-> IO (GValueConstruct o) -> IO (GValueConstruct o)
forall a b. (a -> b) -> a -> b
$ String -> Maybe a -> IO (GValueConstruct o)
forall a o.
GObject a =>
String -> Maybe a -> IO (GValueConstruct o)
B.Properties.constructObjectPropertyObject String
"window" (a -> Maybe a
forall a. a -> Maybe a
P.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
dbgAttrInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.window"
, O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-GLContext.html#g:attr:window"
})
#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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m Bool
gLContextGetDebugEnabled 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
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data 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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Maybe Display)
gLContextGetDisplay 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
$ \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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m Bool
gLContextGetForwardCompatible 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
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data 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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Int32, Int32)
gLContextGetRequiredVersion 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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Maybe GLContext)
gLContextGetSharedContext 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
$ \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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m Bool
gLContextGetUseEs 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
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data 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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Int32, Int32)
gLContextGetVersion 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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m (Maybe Window)
gLContextGetWindow 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
$ \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.OverloadedMethod GLContextGetWindowMethodInfo a signature where
overloadedMethod = gLContextGetWindow
instance O.OverloadedMethodInfo GLContextGetWindowMethodInfo a where
overloadedMethodInfo = P.Just (O.ResolvedSymbolInfo {
O.resolvedSymbolName = "GI.Gdk.Objects.GLContext.gLContextGetWindow",
O.resolvedSymbolURL = "https://hackage.haskell.org/package/gi-gdk-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m Bool
gLContextIsLegacy 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
/= CInt
0) CInt
result
a -> IO ()
forall a. ManagedPtrNewtype a => a -> IO ()
touchManagedPtr a
context
Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
result'
#if defined(ENABLE_OVERLOADING)
data 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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m ()
gLContextMakeCurrent 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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> m ()
gLContextRealize 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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> Bool -> m ()
gLContextSetDebugEnabled a
context 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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> Bool -> m ()
gLContextSetForwardCompatible a
context 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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> Int32 -> Int32 -> m ()
gLContextSetRequiredVersion a
context Int32
major 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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v: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 :: forall (m :: * -> *) a.
(HasCallStack, MonadIO m, IsGLContext a) =>
a -> Int32 -> m ()
gLContextSetUseEs a
context 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.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-3.0.25/docs/GI-Gdk-Objects-GLContext.html#v:gLContextSetUseEs"
})
#endif
foreign import ccall "gdk_gl_context_clear_current" gdk_gl_context_clear_current ::
IO ()
gLContextClearCurrent ::
(B.CallStack.HasCallStack, MonadIO m) =>
m ()
gLContextClearCurrent :: forall (m :: * -> *). (HasCallStack, MonadIO m) => 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 :: forall (m :: * -> *).
(HasCallStack, MonadIO m) =>
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
$ \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