diff options
Diffstat (limited to 'Graphics/Glyph/ExtendedGL')
-rw-r--r-- | Graphics/Glyph/ExtendedGL/Base.hs | 34 | ||||
-rw-r--r-- | Graphics/Glyph/ExtendedGL/Framebuffers.hs | 26 |
2 files changed, 27 insertions, 33 deletions
diff --git a/Graphics/Glyph/ExtendedGL/Base.hs b/Graphics/Glyph/ExtendedGL/Base.hs index 48f61a5..88566f4 100644 --- a/Graphics/Glyph/ExtendedGL/Base.hs +++ b/Graphics/Glyph/ExtendedGL/Base.hs @@ -5,8 +5,8 @@ module Graphics.Glyph.ExtendedGL.Base where import qualified Graphics.Rendering.OpenGL as GL -import Graphics.Rendering.OpenGL.Raw.Core31 -import Graphics.Rendering.OpenGL.Raw.ARB +import Graphics.GL.Core43 +import Graphics.GL.Compatibility30 import Foreign.Marshal.Alloc import Foreign.Ptr @@ -18,6 +18,7 @@ import Control.Monad import Data.StateVar import Unsafe.Coerce +import Data.Proxy data ExPrimitiveMode = Points | Triangles | Lines | Patches deriving (Show,Enum) @@ -40,8 +41,8 @@ class HasParamOfType b t a where class IsPrimitiveModeMarshallable a where marshalPrimitiveMode :: a -> GLuint -castPrimitive :: forall a b t. (IsWrappedPrimitive t a, IsWrappedPrimitive t b) => a -> b -castPrimitive x = wrap unw +castPrimitive :: forall a b t. (IsWrappedPrimitive t a, IsWrappedPrimitive t b) => Proxy t -> a -> b +castPrimitive _ x = wrap unw where unw :: t unw = unwrap x @@ -54,10 +55,10 @@ instance (IsWrappedPrimitive GLenum a) => IsGLEnumMarshallable a where instance IsPrimitiveModeMarshallable ExPrimitiveMode where marshalPrimitiveMode x = case x of - Points -> gl_POINTS - Triangles -> gl_TRIANGLES - Lines -> gl_LINES - Patches -> gl_PATCHES + Points -> GL_POINTS + Triangles -> GL_TRIANGLES + Lines -> GL_LINES + Patches -> GL_PATCHES instance IsPrimitiveModeMarshallable GL.PrimitiveMode where marshalPrimitiveMode x = case x of @@ -75,13 +76,6 @@ instance IsPrimitiveModeMarshallable GL.PrimitiveMode where instance IsPrimitiveModeMarshallable GLuint where marshalPrimitiveMode = id -drawArraysInstanced :: - (IsPrimitiveModeMarshallable a) => - a -> GL.ArrayIndex -> - GL.NumArrayIndices -> - GLsizei -> IO () -drawArraysInstanced = glDrawArraysInstanced . marshalPrimitiveMode - vertexAttributeDivisor :: GL.AttribLocation -> SettableStateVar GLuint vertexAttributeDivisor (GL.AttribLocation loc) = makeSettableStateVar $ \val -> @@ -92,15 +86,15 @@ vertexAttributeDivisor (GL.AttribLocation loc) = patchVertices :: (Integral a) => SettableStateVar a patchVertices = makeSettableStateVar $ \val -> - glPatchParameteri gl_PATCH_VERTICES $ fromIntegral val + glPatchParameteri GL_PATCH_VERTICES $ fromIntegral val {- Returns the maximum number of patches - for a tessilation shader -} maxPatchVertices :: IO CInt maxPatchVertices = alloca $ \ptr -> do - glGetIntegerv gl_MAX_PATCH_VERTICES ptr - peek ptr + glGetIntegerv GL_MAX_PATCH_VERTICES ptr + fromIntegral <$> peek ptr getGLVersion :: IO String getGLVersion = @@ -108,8 +102,8 @@ getGLVersion = x <- a ; y <- b ; return (x,y) in alloca $ \ptr1 -> alloca $ \ptr2 -> do - glGetIntegerv gl_MAJOR_VERSION ptr1 - glGetIntegerv gl_MINOR_VERSION ptr2 + glGetIntegerv GL_MAJOR_VERSION ptr1 + glGetIntegerv GL_MINOR_VERSION ptr2 (v1,v2) <- lift2 (peek ptr1, peek ptr2) return ("OpenGL " ++ show v1 ++ "." ++ show v2) diff --git a/Graphics/Glyph/ExtendedGL/Framebuffers.hs b/Graphics/Glyph/ExtendedGL/Framebuffers.hs index abe9756..a6c2891 100644 --- a/Graphics/Glyph/ExtendedGL/Framebuffers.hs +++ b/Graphics/Glyph/ExtendedGL/Framebuffers.hs @@ -6,8 +6,8 @@ module Graphics.Glyph.ExtendedGL.Framebuffers where -import Graphics.Rendering.OpenGL.Raw.ARB -import Graphics.Rendering.OpenGL.Raw.Core31 +import Graphics.GL.Compatibility30 +import Graphics.GL.Core43 import qualified Graphics.Rendering.OpenGL as GL import Graphics.Glyph.ExtendedGL.Base @@ -46,12 +46,12 @@ instance IsGenerable Renderbuffer where glGenRenderbuffers 1 ptr liftM Renderbuffer $ peek ptr instance IsBindable Renderbuffer where - bind = glBindRenderbuffer gl_RENDERBUFFER . unwrap + bind = glBindRenderbuffer GL_RENDERBUFFER . unwrap data RenderbufferArgument = DepthAttachment instance IsWrappedPrimitive GLenum RenderbufferArgument where - unwrap DepthAttachment = gl_DEPTH_ATTACHMENT + unwrap DepthAttachment = GL_DEPTH_ATTACHMENT renderBufferStorageRaw :: (IsGLEnumMarshallable a, IsGLEnumMarshallable b) => a -> b -> Int -> Int -> IO () renderBufferStorageRaw typ enum w h = glRenderbufferStorage (toGLEnum typ) @@ -59,7 +59,7 @@ renderBufferStorageRaw typ enum w h = glRenderbufferStorage (toGLEnum typ) renderBufferStorage :: (IsGLEnumMarshallable a) => Renderbuffer -> SettableStateVar (a,Int,Int) renderBufferStorage buffer = makeSettableStateVar $ \(en,w,h) -> do bind buffer - renderBufferStorageRaw gl_RENDERBUFFER en w h + renderBufferStorageRaw GL_RENDERBUFFER en w h frameBufferRenderBuffer :: forall a b. (IsFramebuffer a,IsGLEnumMarshallable b) => Renderbuffer -> b -> IO a frameBufferRenderBuffer rb e = do @@ -68,7 +68,7 @@ frameBufferRenderBuffer rb e = do unw :: GLuint unw = unwrap rb bind rb - glFramebufferRenderbuffer enum (toGLEnum e) gl_RENDERBUFFER (unwrap rb) + glFramebufferRenderbuffer enum (toGLEnum e) GL_RENDERBUFFER (unwrap rb) return $ wrap unw where test :: a @@ -79,14 +79,14 @@ data FramebufferParameter = DefaultWidth | DefaultHeight instance IsWrappedPrimitive GLenum FramebufferParameter where unwrap p = case p of - DefaultWidth -> gl_FRAMEBUFFER_DEFAULT_WIDTH - DefaultHeight -> gl_FRAMEBUFFER_DEFAULT_HEIGHT - wrap x | x == gl_FRAMEBUFFER_DEFAULT_WIDTH = DefaultWidth - | x == gl_FRAMEBUFFER_DEFAULT_HEIGHT = DefaultHeight + DefaultWidth -> GL_FRAMEBUFFER_DEFAULT_WIDTH + DefaultHeight -> GL_FRAMEBUFFER_DEFAULT_HEIGHT + wrap x | x == GL_FRAMEBUFFER_DEFAULT_WIDTH = DefaultWidth + | x == GL_FRAMEBUFFER_DEFAULT_HEIGHT = DefaultHeight | otherwise = undefined instance HasIntegerParam GLenum DrawFramebuffer where - parami p fb = framebufferBasicParameteri gl_DRAW_FRAMEBUFFER fb p + parami p fb = framebufferBasicParameteri GL_DRAW_FRAMEBUFFER fb p {- Has parameters of type GLuint which are acessable by the data FramebufferParameter for - the type DrawFramebuffer -} @@ -99,11 +99,11 @@ instance IsGenerable DrawFramebuffer where liftM DrawFramebuffer $ peek ptr instance IsBindable DrawFramebuffer where - bind (DrawFramebuffer fb) = glBindFramebuffer gl_DRAW_FRAMEBUFFER fb + bind (DrawFramebuffer fb) = glBindFramebuffer GL_DRAW_FRAMEBUFFER fb instance IsWrappedPrimitive GLuint DrawFramebuffer where unwrap (DrawFramebuffer fb) = fb wrap = DrawFramebuffer instance IsFramebuffer DrawFramebuffer where - getType _ = gl_DRAW_FRAMEBUFFER + getType _ = GL_DRAW_FRAMEBUFFER |