-------------------------------------------------------------------------------- -- | -- Module : Graphics.Rendering.OGL.GL.VertexSpec -- Copyright : (c) Sven Panne 2002-2006 -- License : BSD-style (see the file libraries/OpenGL/LICENSE) -- -- Maintainer : sven.panne@aedion.de -- Stability : stable -- Portability : portable -- -- This module corresponds to section 2.7 (Vertex Specification) of the -- OpenGL 2.1 specs. -- -------------------------------------------------------------------------------- module Graphics.Rendering.OGL.GL.VertexSpec ( -- * Vertex Coordinates Vertex(..), VertexComponent, Vertex2(..), Vertex3(..), Vertex4(..), -- * Auxiliary Vertex Attributes -- $AuxiliaryVertexAttributes -- ** Texture Coordinates currentTextureCoords, TexCoord(..), TexCoordComponent, TexCoord1(..), TexCoord2(..), TexCoord3(..), TexCoord4(..), -- ** Normal currentNormal, Normal(..), NormalComponent, Normal3(..), -- ** Fog Coordinate currentFogCoord, FogCoord(..), FogCoordComponent, FogCoord1(..), -- ** Color and Secondary Color rgbaMode, currentColor, Color(..), currentSecondaryColor, SecondaryColor(..), ColorComponent, Color3(..), Color4(..), currentIndex, Index(..), IndexComponent, Index1(..), -- * Generic Vertex Attributes AttribLocation(..), VertexAttrib, VertexAttribComponent(..), -- * Texture Units TextureUnit(..), maxTextureUnit ) where import Data.Int import Data.Word import Foreign.Ptr ( Ptr, castPtr ) import Foreign.Storable ( Storable(..) ) import Foreign.Storable ( Storable(..) ) import Graphics.Rendering.OGL.Monad import Graphics.Rendering.OGL.GL.BasicTypes ( GLenum, GLbyte, GLshort, GLint, GLubyte, GLushort, GLuint, GLfloat, GLdouble ) import Graphics.Rendering.OGL.GL.Extensions ( FunPtr, unsafePerformIO, Invoker, getProcAddress ) import Graphics.Rendering.OGL.GL.GLboolean ( unmarshalGLboolean ) import Graphics.Rendering.OGL.GL.PeekPoke ( poke1, poke2, poke3, poke4, peek1, peek2, peek3, peek4 ) import Graphics.Rendering.OGL.GL.QueryUtils ( GetPName(GetCurrentTextureCoords, GetCurrentNormal, GetCurrentFogCoord, GetCurrentColor, GetCurrentSecondaryColor, GetCurrentIndex, GetMaxTextureUnits,GetRGBAMode), getBoolean1, getInteger1, getEnum1, getFloat1, getFloat3, getFloat4 ) import Graphics.Rendering.OGL.GL.StateVar ( GettableStateVar, makeGettableStateVar, StateVar, makeStateVar ) import Graphics.Rendering.OGL.GL.Texturing.TextureUnit ( TextureUnit(..), marshalTextureUnit, unmarshalTextureUnit ) -------------------------------------------------------------------------------- #include "HsOpenGLExt.h" #include "HsOpenGLTypes.h" -------------------------------------------------------------------------------- -- | The class of all types which can be used as a vertex coordinate. class VertexComponent a where vertex2 :: a -> a -> PrimitiveGL () vertex3 :: a -> a -> a -> PrimitiveGL () vertex4 :: a -> a -> a -> a -> PrimitiveGL () vertex2v :: Ptr a -> PrimitiveGL () vertex3v :: Ptr a -> PrimitiveGL () vertex4v :: Ptr a -> PrimitiveGL () -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glVertex2s" glVertex2s :: GLshort -> GLshort -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex3s" glVertex3s :: GLshort -> GLshort -> GLshort -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex4s" glVertex4s :: GLshort -> GLshort -> GLshort -> GLshort -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex2sv" glVertex2sv :: Ptr GLshort -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex3sv" glVertex3sv :: Ptr GLshort -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex4sv" glVertex4sv :: Ptr GLshort -> PrimitiveGL () instance VertexComponent GLshort_ where vertex2 = glVertex2s vertex3 = glVertex3s vertex4 = glVertex4s vertex2v = glVertex2sv vertex3v = glVertex3sv vertex4v = glVertex4sv -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glVertex2i" glVertex2i :: GLint -> GLint -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex3i" glVertex3i :: GLint -> GLint -> GLint -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex4i" glVertex4i :: GLint -> GLint -> GLint -> GLint -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex2iv" glVertex2iv :: Ptr GLint -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex3iv" glVertex3iv :: Ptr GLint -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex4iv" glVertex4iv :: Ptr GLint -> PrimitiveGL () instance VertexComponent GLint_ where vertex2 = glVertex2i vertex3 = glVertex3i vertex4 = glVertex4i vertex2v = glVertex2iv vertex3v = glVertex3iv vertex4v = glVertex4iv -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glVertex2f" glVertex2f :: GLfloat -> GLfloat -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex3f" glVertex3f :: GLfloat -> GLfloat -> GLfloat -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex4f" glVertex4f :: GLfloat -> GLfloat -> GLfloat -> GLfloat -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex2fv" glVertex2fv :: Ptr GLfloat -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex3fv" glVertex3fv :: Ptr GLfloat -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex4fv" glVertex4fv :: Ptr GLfloat -> PrimitiveGL () instance VertexComponent GLfloat_ where vertex2 = glVertex2f vertex3 = glVertex3f vertex4 = glVertex4f vertex2v = glVertex2fv vertex3v = glVertex3fv vertex4v = glVertex4fv -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glVertex2d" glVertex2d :: GLdouble -> GLdouble -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex3d" glVertex3d :: GLdouble -> GLdouble -> GLdouble -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex4d" glVertex4d :: GLdouble -> GLdouble -> GLdouble -> GLdouble -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex2dv" glVertex2dv :: Ptr GLdouble -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex3dv" glVertex3dv :: Ptr GLdouble -> PrimitiveGL () foreign import CALLCONV unsafe "glVertex4dv" glVertex4dv :: Ptr GLdouble -> PrimitiveGL () instance VertexComponent GLdouble_ where vertex2 = glVertex2d vertex3 = glVertex3d vertex4 = glVertex4d vertex2v = glVertex2dv vertex3v = glVertex3dv vertex4v = glVertex4dv -------------------------------------------------------------------------------- -- | Specify the (/x/, /y/, /z/, /w/) coordinates of a four-dimensional vertex. -- This must only be done during -- 'Graphics.Rendering.OGL.GL.BeginEnd.renderPrimitive', otherwise the -- behaviour is unspecified. The current values of the auxiliary vertex -- attributes are associated with the vertex. -- -- Note that there is no such thing as a \"current vertex\" which could be -- retrieved. class Vertex a where vertex :: a -> PrimitiveGL () vertexv :: Ptr a -> PrimitiveGL () -- | A vertex with /z/=0 and /w/=1. data Vertex2 a = Vertex2 !a !a deriving ( Eq, Ord, Show ) instance VertexComponent a => Vertex (Vertex2 a) where vertex (Vertex2 x y) = vertex2 x y vertexv = vertex2v . (castPtr :: Ptr (Vertex2 b) -> Ptr b) instance Storable a => Storable (Vertex2 a) where sizeOf ~(Vertex2 x _) = 2 * sizeOf x alignment ~(Vertex2 x _) = alignment x peek = peek2 Vertex2 . castPtr poke ptr (Vertex2 x y) = poke2 (castPtr ptr) x y -- | A vertex with /w/=1. data Vertex3 a = Vertex3 !a !a !a deriving ( Eq, Ord, Show ) instance VertexComponent a => Vertex (Vertex3 a) where vertex (Vertex3 x y z) = vertex3 x y z vertexv = vertex3v . (castPtr :: Ptr (Vertex3 b) -> Ptr b) instance Storable a => Storable (Vertex3 a) where sizeOf ~(Vertex3 x _ _) = 3 * sizeOf x alignment ~(Vertex3 x _ _) = alignment x peek = peek3 Vertex3 . castPtr poke ptr (Vertex3 x y z) = poke3 (castPtr ptr) x y z -- | A fully-fledged four-dimensional vertex. data Vertex4 a = Vertex4 !a !a !a !a deriving ( Eq, Ord, Show ) instance VertexComponent a => Vertex (Vertex4 a) where vertex (Vertex4 x y z w) = vertex4 x y z w vertexv = vertex4v . (castPtr :: Ptr (Vertex4 b) -> Ptr b) instance Storable a => Storable (Vertex4 a) where sizeOf ~(Vertex4 x _ _ _) = 4 * sizeOf x alignment ~(Vertex4 x _ _ _) = alignment x peek = peek4 Vertex4 . castPtr poke ptr (Vertex4 x y z w) = poke4 (castPtr ptr) x y z w -------------------------------------------------------------------------------- -- $AuxiliaryVertexAttributes -- Apart from its coordinates in four-dimensional space, every vertex has -- associated /auxiliary attributes/: Its texture coordinates, a normal, a -- fog coordinate, and a color plus a secondary color. For every attribute, the -- OpenGL state contains its current value, which can be changed at any time. -- -- Every attribute has a \"natural\" format via which it can be manipulated -- directly as part of the OpenGL state, e.g. the current texture coordinates -- are internally handled as @'TexCoord4' 'GLfloat'@. Different formats are -- converted to this format, e.g. the /s/, /r/, and /t/ coordinates of a -- @'TexCoord3' 'GLint'@ are converted to floating point values and a /q/ -- coordinate of 1.0 is implicitly assumed. -- -- Consequently, the vast majority of classes, functions, and data types in this -- module are for convenience only and offer no additional functionality. -------------------------------------------------------------------------------- -- | The current texture coordinates (/s/, /t/, /r/, /q/) for the current -- texture unit (see 'Graphics.Rendering.OGL.GL.CoordTrans.activeTexture'). -- The initial value is (0,0,0,1) for all texture units. currentTextureCoords :: StateVar (TexCoord4 GLfloat) currentTextureCoords = makeStateVar (getFloat4 TexCoord4 GetCurrentTextureCoords) (runPrimitive . texCoord) -------------------------------------------------------------------------------- -- | The class of all types which can be used as a texture coordinate. class TexCoordComponent a where texCoord1 :: MonadGL m => a -> m () texCoord2 :: MonadGL m => a -> a -> m () texCoord3 :: MonadGL m => a -> a -> a -> m () texCoord4 :: MonadGL m => a -> a -> a -> a -> m () texCoord1v :: MonadGL m => Ptr a -> m () texCoord2v :: MonadGL m => Ptr a -> m () texCoord3v :: MonadGL m => Ptr a -> m () texCoord4v :: MonadGL m => Ptr a -> m () multiTexCoord1 :: MonadGL m => GLenum -> a -> m () multiTexCoord2 :: MonadGL m => GLenum -> a -> a -> m () multiTexCoord3 :: MonadGL m => GLenum -> a -> a -> a -> m () multiTexCoord4 :: MonadGL m => GLenum -> a -> a -> a -> a -> m () multiTexCoord1v :: MonadGL m => GLenum -> Ptr a -> m () multiTexCoord2v :: MonadGL m => GLenum -> Ptr a -> m () multiTexCoord3v :: MonadGL m => GLenum -> Ptr a -> m () multiTexCoord4v :: MonadGL m => GLenum -> Ptr a -> m () -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glTexCoord1s" glTexCoord1s :: GLshort -> IO () foreign import CALLCONV unsafe "glTexCoord2s" glTexCoord2s :: GLshort -> GLshort -> IO () foreign import CALLCONV unsafe "glTexCoord3s" glTexCoord3s :: GLshort -> GLshort -> GLshort -> IO () foreign import CALLCONV unsafe "glTexCoord4s" glTexCoord4s :: GLshort -> GLshort -> GLshort -> GLshort -> IO () foreign import CALLCONV unsafe "glTexCoord1sv" glTexCoord1sv :: Ptr GLshort -> IO () foreign import CALLCONV unsafe "glTexCoord2sv" glTexCoord2sv :: Ptr GLshort -> IO () foreign import CALLCONV unsafe "glTexCoord3sv" glTexCoord3sv :: Ptr GLshort -> IO () foreign import CALLCONV unsafe "glTexCoord4sv" glTexCoord4sv :: Ptr GLshort -> IO () EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord1sARB,GLenum -> GLshort -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord2sARB,GLenum -> GLshort -> GLshort -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord3sARB,GLenum -> GLshort -> GLshort -> GLshort -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord4sARB,GLenum -> GLshort -> GLshort -> GLshort -> GLshort -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord1svARB,GLenum -> Ptr GLshort -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord2svARB,GLenum -> Ptr GLshort -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord3svARB,GLenum -> Ptr GLshort -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord4svARB,GLenum -> Ptr GLshort -> IO ()) instance TexCoordComponent GLshort_ where texCoord1 = liftIO . glTexCoord1s texCoord2 a b = liftIO $ glTexCoord2s a b texCoord3 a b c = liftIO $ glTexCoord3s a b c texCoord4 a b c d = liftIO $ glTexCoord4s a b c d texCoord1v = liftIO . glTexCoord1sv texCoord2v = liftIO . glTexCoord2sv texCoord3v = liftIO . glTexCoord3sv texCoord4v = liftIO . glTexCoord4sv multiTexCoord1 x a = liftIO $ glMultiTexCoord1sARB x a multiTexCoord2 x a b = liftIO $ glMultiTexCoord2sARB x a b multiTexCoord3 x a b c = liftIO $ glMultiTexCoord3sARB x a b c multiTexCoord4 x a b c d = liftIO $ glMultiTexCoord4sARB x a b c d multiTexCoord1v x a = liftIO $ glMultiTexCoord1svARB x a multiTexCoord2v x a = liftIO $ glMultiTexCoord2svARB x a multiTexCoord3v x a = liftIO $ glMultiTexCoord3svARB x a multiTexCoord4v x a = liftIO $ glMultiTexCoord4svARB x a -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glTexCoord1i" glTexCoord1i :: GLint -> IO () foreign import CALLCONV unsafe "glTexCoord2i" glTexCoord2i :: GLint -> GLint -> IO () foreign import CALLCONV unsafe "glTexCoord3i" glTexCoord3i :: GLint -> GLint -> GLint -> IO () foreign import CALLCONV unsafe "glTexCoord4i" glTexCoord4i :: GLint -> GLint -> GLint -> GLint -> IO () foreign import CALLCONV unsafe "glTexCoord1iv" glTexCoord1iv :: Ptr GLint -> IO () foreign import CALLCONV unsafe "glTexCoord2iv" glTexCoord2iv :: Ptr GLint -> IO () foreign import CALLCONV unsafe "glTexCoord3iv" glTexCoord3iv :: Ptr GLint -> IO () foreign import CALLCONV unsafe "glTexCoord4iv" glTexCoord4iv :: Ptr GLint -> IO () EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord1iARB,GLenum -> GLint -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord2iARB,GLenum -> GLint -> GLint -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord3iARB,GLenum -> GLint -> GLint -> GLint -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord4iARB,GLenum -> GLint -> GLint -> GLint -> GLint -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord1ivARB,GLenum -> Ptr GLint -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord2ivARB,GLenum -> Ptr GLint -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord3ivARB,GLenum -> Ptr GLint -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord4ivARB,GLenum -> Ptr GLint -> IO ()) instance TexCoordComponent GLint_ where texCoord1 = liftIO . glTexCoord1i texCoord2 a b = liftIO $ glTexCoord2i a b texCoord3 a b c = liftIO $ glTexCoord3i a b c texCoord4 a b c d = liftIO $ glTexCoord4i a b c d texCoord1v = liftIO . glTexCoord1iv texCoord2v = liftIO . glTexCoord2iv texCoord3v = liftIO . glTexCoord3iv texCoord4v = liftIO . glTexCoord4iv multiTexCoord1 x a = liftIO $ glMultiTexCoord1iARB x a multiTexCoord2 x a b = liftIO $ glMultiTexCoord2iARB x a b multiTexCoord3 x a b c = liftIO $ glMultiTexCoord3iARB x a b c multiTexCoord4 x a b c d = liftIO $ glMultiTexCoord4iARB x a b c d multiTexCoord1v x a = liftIO $ glMultiTexCoord1ivARB x a multiTexCoord2v x a = liftIO $ glMultiTexCoord2ivARB x a multiTexCoord3v x a = liftIO $ glMultiTexCoord3ivARB x a multiTexCoord4v x a = liftIO $ glMultiTexCoord4ivARB x a -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glTexCoord1f" glTexCoord1f :: GLfloat -> IO () foreign import CALLCONV unsafe "glTexCoord2f" glTexCoord2f :: GLfloat -> GLfloat -> IO () foreign import CALLCONV unsafe "glTexCoord3f" glTexCoord3f :: GLfloat -> GLfloat -> GLfloat -> IO () foreign import CALLCONV unsafe "glTexCoord4f" glTexCoord4f :: GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO () foreign import CALLCONV unsafe "glTexCoord1fv" glTexCoord1fv :: Ptr GLfloat -> IO () foreign import CALLCONV unsafe "glTexCoord2fv" glTexCoord2fv :: Ptr GLfloat -> IO () foreign import CALLCONV unsafe "glTexCoord3fv" glTexCoord3fv :: Ptr GLfloat -> IO () foreign import CALLCONV unsafe "glTexCoord4fv" glTexCoord4fv :: Ptr GLfloat -> IO () EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord1fARB,GLenum -> GLfloat -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord2fARB,GLenum -> GLfloat -> GLfloat -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord3fARB,GLenum -> GLfloat -> GLfloat -> GLfloat -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord4fARB,GLenum -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord1fvARB,GLenum -> Ptr GLfloat -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord2fvARB,GLenum -> Ptr GLfloat -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord3fvARB,GLenum -> Ptr GLfloat -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord4fvARB,GLenum -> Ptr GLfloat -> IO ()) instance TexCoordComponent GLfloat_ where texCoord1 = liftIO . glTexCoord1f texCoord2 a b = liftIO $ glTexCoord2f a b texCoord3 a b c = liftIO $ glTexCoord3f a b c texCoord4 a b c d = liftIO $ glTexCoord4f a b c d texCoord1v = liftIO . glTexCoord1fv texCoord2v = liftIO . glTexCoord2fv texCoord3v = liftIO . glTexCoord3fv texCoord4v = liftIO . glTexCoord4fv multiTexCoord1 x a = liftIO $ glMultiTexCoord1fARB x a multiTexCoord2 x a b = liftIO $ glMultiTexCoord2fARB x a b multiTexCoord3 x a b c = liftIO $ glMultiTexCoord3fARB x a b c multiTexCoord4 x a b c d = liftIO $ glMultiTexCoord4fARB x a b c d multiTexCoord1v x a = liftIO $ glMultiTexCoord1fvARB x a multiTexCoord2v x a = liftIO $ glMultiTexCoord2fvARB x a multiTexCoord3v x a = liftIO $ glMultiTexCoord3fvARB x a multiTexCoord4v x a = liftIO $ glMultiTexCoord4fvARB x a -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glTexCoord1d" glTexCoord1d :: GLdouble -> IO () foreign import CALLCONV unsafe "glTexCoord2d" glTexCoord2d :: GLdouble -> GLdouble -> IO () foreign import CALLCONV unsafe "glTexCoord3d" glTexCoord3d :: GLdouble -> GLdouble -> GLdouble -> IO () foreign import CALLCONV unsafe "glTexCoord4d" glTexCoord4d :: GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO () foreign import CALLCONV unsafe "glTexCoord1dv" glTexCoord1dv :: Ptr GLdouble -> IO () foreign import CALLCONV unsafe "glTexCoord2dv" glTexCoord2dv :: Ptr GLdouble -> IO () foreign import CALLCONV unsafe "glTexCoord3dv" glTexCoord3dv :: Ptr GLdouble -> IO () foreign import CALLCONV unsafe "glTexCoord4dv" glTexCoord4dv :: Ptr GLdouble -> IO () EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord1dARB,GLenum -> GLdouble -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord2dARB,GLenum -> GLdouble -> GLdouble -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord3dARB,GLenum -> GLdouble -> GLdouble -> GLdouble -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord4dARB,GLenum -> GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord1dvARB,GLenum -> Ptr GLdouble -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord2dvARB,GLenum -> Ptr GLdouble -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord3dvARB,GLenum -> Ptr GLdouble -> IO ()) EXTENSION_ENTRY("GL_ARB_multitexture or OpenGL 1.3",glMultiTexCoord4dvARB,GLenum -> Ptr GLdouble -> IO ()) instance TexCoordComponent GLdouble_ where texCoord1 = liftIO . glTexCoord1d texCoord2 a b = liftIO $ glTexCoord2d a b texCoord3 a b c = liftIO $ glTexCoord3d a b c texCoord4 a b c d = liftIO $ glTexCoord4d a b c d texCoord1v = liftIO . glTexCoord1dv texCoord2v = liftIO . glTexCoord2dv texCoord3v = liftIO . glTexCoord3dv texCoord4v = liftIO . glTexCoord4dv multiTexCoord1 x a = liftIO $ glMultiTexCoord1dARB x a multiTexCoord2 x a b = liftIO $ glMultiTexCoord2dARB x a b multiTexCoord3 x a b c = liftIO $ glMultiTexCoord3dARB x a b c multiTexCoord4 x a b c d = liftIO $ glMultiTexCoord4dARB x a b c d multiTexCoord1v x a = liftIO $ glMultiTexCoord1dvARB x a multiTexCoord2v x a = liftIO $ glMultiTexCoord2dvARB x a multiTexCoord3v x a = liftIO $ glMultiTexCoord3dvARB x a multiTexCoord4v x a = liftIO $ glMultiTexCoord4dvARB x a -------------------------------------------------------------------------------- -- | Change the current texture coordinates of the current or given texture -- unit. class TexCoord a where texCoord :: MonadGL m => a -> m () texCoordv :: MonadGL m => Ptr a -> m () multiTexCoord :: MonadGL m => TextureUnit -> a -> m () multiTexCoordv :: MonadGL m => TextureUnit -> Ptr a -> m () -- | Texture coordinates with /t/=0, /r/=0, and /q/=1. newtype TexCoord1 a = TexCoord1 a deriving ( Eq, Ord, Show ) instance TexCoordComponent a => TexCoord (TexCoord1 a) where texCoord (TexCoord1 s) = texCoord1 s texCoordv = texCoord1v . (castPtr :: Ptr (TexCoord1 b) -> Ptr b) multiTexCoord u (TexCoord1 s) = multiTexCoord1 (marshalTextureUnit u) s multiTexCoordv u = multiTexCoord1v (marshalTextureUnit u) . (castPtr :: Ptr (TexCoord1 b) -> Ptr b) instance Storable a => Storable (TexCoord1 a) where sizeOf ~(TexCoord1 s) = sizeOf s alignment ~(TexCoord1 s) = alignment s peek = peek1 TexCoord1 . castPtr poke ptr (TexCoord1 s) = poke1 (castPtr ptr) s -- | Texture coordinates with /r/=0 and /q/=1. data TexCoord2 a = TexCoord2 !a !a deriving ( Eq, Ord, Show ) instance TexCoordComponent a => TexCoord (TexCoord2 a) where texCoord (TexCoord2 s t) = texCoord2 s t texCoordv = texCoord2v . (castPtr :: Ptr (TexCoord2 b) -> Ptr b) multiTexCoord u (TexCoord2 s t) = multiTexCoord2 (marshalTextureUnit u) s t multiTexCoordv u = multiTexCoord2v (marshalTextureUnit u) . (castPtr :: Ptr (TexCoord2 b) -> Ptr b) instance Storable a => Storable (TexCoord2 a) where sizeOf ~(TexCoord2 s _) = 2 * sizeOf s alignment ~(TexCoord2 s _) = alignment s peek = peek2 TexCoord2 . castPtr poke ptr (TexCoord2 s t) = poke2 (castPtr ptr) s t -- | Texture coordinates with /q/=1. data TexCoord3 a = TexCoord3 !a !a !a deriving ( Eq, Ord, Show ) instance TexCoordComponent a => TexCoord (TexCoord3 a) where texCoord (TexCoord3 s t r) = texCoord3 s t r texCoordv = texCoord3v . (castPtr :: Ptr (TexCoord3 b) -> Ptr b) multiTexCoord u (TexCoord3 s t r) = multiTexCoord3 (marshalTextureUnit u) s t r multiTexCoordv u = multiTexCoord3v (marshalTextureUnit u) . (castPtr :: Ptr (TexCoord3 b) -> Ptr b) instance Storable a => Storable (TexCoord3 a) where sizeOf ~(TexCoord3 s _ _) = 3 * sizeOf s alignment ~(TexCoord3 s _ _) = alignment s peek = peek3 TexCoord3 . castPtr poke ptr (TexCoord3 s t r) = poke3 (castPtr ptr) s t r -- | Fully-fledged four-dimensional texture coordinates. data TexCoord4 a = TexCoord4 !a !a !a !a deriving ( Eq, Ord, Show ) instance TexCoordComponent a => TexCoord (TexCoord4 a) where texCoord (TexCoord4 s t r q) = texCoord4 s t r q texCoordv = texCoord4v . (castPtr :: Ptr (TexCoord4 b) -> Ptr b) multiTexCoord u (TexCoord4 s t r q) = multiTexCoord4 (marshalTextureUnit u) s t r q multiTexCoordv u = multiTexCoord4v (marshalTextureUnit u) . (castPtr :: Ptr (TexCoord4 b) -> Ptr b) instance Storable a => Storable (TexCoord4 a) where sizeOf ~(TexCoord4 s _ _ _) = 4 * sizeOf s alignment ~(TexCoord4 s _ _ _) = alignment s peek = peek4 TexCoord4 . castPtr poke ptr (TexCoord4 s t r q) = poke4 (castPtr ptr) s t r q -------------------------------------------------------------------------------- -- | The current normal (/x/, /y/, /z/). The initial value is the unit vector -- (0, 0, 1). currentNormal :: StateVar (Normal3 GLfloat) currentNormal = makeStateVar (getFloat3 Normal3 GetCurrentNormal) (runPrimitive . normal) -------------------------------------------------------------------------------- -- | The class of all types which can be used as a component of a normal. class NormalComponent a where normal3 :: MonadGL m => a -> a -> a -> m () normal3v :: MonadGL m => Ptr a -> m () -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glNormal3b" glNormal3b :: GLbyte -> GLbyte -> GLbyte -> IO () foreign import CALLCONV unsafe "glNormal3bv" glNormal3bv :: Ptr GLbyte -> IO () instance NormalComponent GLbyte_ where normal3 a b c = liftIO $ glNormal3b a b c normal3v a = liftIO $ glNormal3bv a -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glNormal3s" glNormal3s :: GLshort -> GLshort -> GLshort -> IO () foreign import CALLCONV unsafe "glNormal3sv" glNormal3sv :: Ptr GLshort -> IO () instance NormalComponent GLshort_ where normal3 a b c = liftIO $ glNormal3s a b c normal3v a = liftIO $ glNormal3sv a -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glNormal3i" glNormal3i :: GLint -> GLint -> GLint -> IO () foreign import CALLCONV unsafe "glNormal3iv" glNormal3iv :: Ptr GLint -> IO () instance NormalComponent GLint_ where normal3 a b c = liftIO $ glNormal3i a b c normal3v a = liftIO $ glNormal3iv a -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glNormal3f" glNormal3f :: GLfloat -> GLfloat -> GLfloat -> IO () foreign import CALLCONV unsafe "glNormal3fv" glNormal3fv :: Ptr GLfloat -> IO () instance NormalComponent GLfloat_ where normal3 a b c = liftIO $ glNormal3f a b c normal3v a = liftIO $ glNormal3fv a -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glNormal3d" glNormal3d :: GLdouble -> GLdouble -> GLdouble -> IO () foreign import CALLCONV unsafe "glNormal3dv" glNormal3dv :: Ptr GLdouble -> IO () instance NormalComponent GLdouble_ where normal3 a b c = liftIO $ glNormal3d a b c normal3v a = liftIO $ glNormal3dv a -------------------------------------------------------------------------------- -- | Change the current normal. Integral arguments are converted to -- floating-point with a linear mapping that maps the most positive -- representable integer value to 1.0, and the most negative representable -- integer value to -1.0. -- -- Normals specified with 'normal' or 'normalv' need not have unit length. -- If 'Graphics.Rendering.OGL.GL.CoordTrans.normalize' is enabled, then -- normals of any length specified with 'normal' or 'normalv' are normalized -- after transformation. If -- 'Graphics.Rendering.OGL.GL.CoordTrans.rescaleNormal' is enabled, normals -- are scaled by a scaling factor derived from the modelview matrix. -- 'Graphics.Rendering.OGL.GL.CoordTrans.rescaleNormal' requires that the -- originally specified normals were of unit length, and that the modelview -- matrix contains only uniform scales for proper results. Normalization is -- initially disabled. class Normal a where normal :: MonadGL m => a -> m () normalv :: MonadGL m => Ptr a -> m () -- A three-dimensional normal. data Normal3 a = Normal3 !a !a !a deriving ( Eq, Ord, Show ) instance NormalComponent a => Normal (Normal3 a) where normal (Normal3 x y z) = normal3 x y z normalv = normal3v . (castPtr :: Ptr (Normal3 b) -> Ptr b) instance Storable a => Storable (Normal3 a) where sizeOf ~(Normal3 x _ _) = 3 * sizeOf x alignment ~(Normal3 x _ _) = alignment x peek = peek3 Normal3 . castPtr poke ptr (Normal3 x y z) = poke3 (castPtr ptr) x y z -------------------------------------------------------------------------------- -- | The current fog coordinate. The initial value is 0. currentFogCoord :: StateVar (FogCoord1 GLfloat) currentFogCoord = makeStateVar (getFloat1 FogCoord1 GetCurrentFogCoord) (runPrimitive . fogCoord) -------------------------------------------------------------------------------- -- | The class of all types which can be used as the fog coordinate. class FogCoordComponent a where fogCoord1 :: MonadGL m => a -> m () fogCoord1v :: MonadGL m => Ptr a -> m () instance Storable a => Storable (FogCoord1 a) where sizeOf ~(FogCoord1 c) = sizeOf c alignment ~(FogCoord1 c) = alignment c peek = peek1 FogCoord1 . castPtr poke ptr (FogCoord1 c) = poke1 (castPtr ptr) c -------------------------------------------------------------------------------- EXTENSION_ENTRY("GL_EXT_fog_coord or OpenGL 1.4",glFogCoordfEXT,GLfloat -> IO ()) EXTENSION_ENTRY("GL_EXT_fog_coord or OpenGL 1.4",glFogCoordfvEXT,Ptr GLfloat -> IO ()) instance FogCoordComponent GLfloat_ where fogCoord1 = liftIO . glFogCoordfEXT fogCoord1v = liftIO . glFogCoordfvEXT -------------------------------------------------------------------------------- EXTENSION_ENTRY("GL_EXT_fog_coord or OpenGL 1.4",glFogCoorddEXT,GLdouble -> IO ()) EXTENSION_ENTRY("GL_EXT_fog_coord or OpenGL 1.4",glFogCoorddvEXT,Ptr GLdouble -> IO ()) instance FogCoordComponent GLdouble_ where fogCoord1 = liftIO . glFogCoorddEXT fogCoord1v = liftIO . glFogCoorddvEXT -------------------------------------------------------------------------------- -- | Change the current fog coordinate. class FogCoord a where fogCoord :: MonadGL m => a -> m () fogCoordv :: MonadGL m => Ptr a -> m () -- | A fog coordinate. newtype FogCoord1 a = FogCoord1 a deriving ( Eq, Ord, Show ) instance FogCoordComponent a => FogCoord (FogCoord1 a) where fogCoord (FogCoord1 c) = fogCoord1 c fogCoordv = fogCoord1v . (castPtr :: Ptr (FogCoord1 b) -> Ptr b) -------------------------------------------------------------------------------- -- | If 'rgbaMode' contains 'True', the color buffers store RGBA value. If -- color indexes are stored, it contains 'False'. rgbaMode :: GettableStateVar Bool rgbaMode = makeGettableStateVar (getBoolean1 unmarshalGLboolean GetRGBAMode) -------------------------------------------------------------------------------- -- The current color (/R/, /G/, /B/, /A/). The initial value is (1, 1, 1, 1). -- Note that this state variable is significant only when the GL is in RGBA -- mode. currentColor :: StateVar (Color4 GLfloat) currentColor = makeStateVar (getFloat4 Color4 GetCurrentColor) (runPrimitive . color) -- The current secondary color (/R/, /G/, /B/). The initial value is (0, 0, 0). -- Note that this state variable is significant only when the GL is in RGBA -- mode. currentSecondaryColor :: StateVar (Color3 GLfloat) currentSecondaryColor = makeStateVar (do Color4 r g b _ <- getFloat4 Color4 GetCurrentSecondaryColor return $ Color3 r g b) (runPrimitive . secondaryColor) -------------------------------------------------------------------------------- -- | The class of all types which can be used as a color component. class ColorComponent a where color3 :: MonadGL m => a -> a -> a -> m () color4 :: MonadGL m => a -> a -> a -> a -> m () color3v :: MonadGL m => Ptr a -> m () color4v :: MonadGL m => Ptr a -> m () secondaryColor3 :: MonadGL m => a -> a -> a -> m () secondaryColor3v :: MonadGL m => Ptr a -> m () -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glColor3b" glColor3b :: GLbyte -> GLbyte -> GLbyte -> IO () foreign import CALLCONV unsafe "glColor4b" glColor4b :: GLbyte -> GLbyte -> GLbyte -> GLbyte -> IO () foreign import CALLCONV unsafe "glColor3bv" glColor3bv :: Ptr GLbyte -> IO () foreign import CALLCONV unsafe "glColor4bv" glColor4bv :: Ptr GLbyte -> IO () EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3bEXT,GLbyte -> GLbyte -> GLbyte -> IO ()) EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3bvEXT,Ptr GLbyte -> IO ()) instance ColorComponent GLbyte_ where color3 r g b = liftIO $ glColor3b r g b color4 r g b a = liftIO $ glColor4b r g b a color3v = liftIO . glColor3bv color4v = liftIO . glColor4bv secondaryColor3 r g b = liftIO $ glSecondaryColor3bEXT r g b secondaryColor3v = liftIO . glSecondaryColor3bvEXT -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glColor3s" glColor3s :: GLshort -> GLshort -> GLshort -> IO () foreign import CALLCONV unsafe "glColor4s" glColor4s :: GLshort -> GLshort -> GLshort -> GLshort -> IO () foreign import CALLCONV unsafe "glColor3sv" glColor3sv :: Ptr GLshort -> IO () foreign import CALLCONV unsafe "glColor4sv" glColor4sv :: Ptr GLshort -> IO () EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3sEXT,GLshort -> GLshort -> GLshort -> IO ()) EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3svEXT,Ptr GLshort -> IO ()) instance ColorComponent GLshort_ where color3 r g b = liftIO $ glColor3s r g b color4 r g b a = liftIO $ glColor4s r g b a color3v = liftIO . glColor3sv color4v = liftIO . glColor4sv secondaryColor3 r g b = liftIO $ glSecondaryColor3sEXT r g b secondaryColor3v = liftIO . glSecondaryColor3svEXT -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glColor3i" glColor3i :: GLint -> GLint -> GLint -> IO () foreign import CALLCONV unsafe "glColor4i" glColor4i :: GLint -> GLint -> GLint -> GLint -> IO () foreign import CALLCONV unsafe "glColor3iv" glColor3iv :: Ptr GLint -> IO () foreign import CALLCONV unsafe "glColor4iv" glColor4iv :: Ptr GLint -> IO () EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3iEXT,GLint -> GLint -> GLint -> IO ()) EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3ivEXT,Ptr GLint -> IO ()) instance ColorComponent GLint_ where color3 r g b = liftIO $ glColor3i r g b color4 r g b a = liftIO $ glColor4i r g b a color3v = liftIO . glColor3iv color4v = liftIO . glColor4iv secondaryColor3 r g b = liftIO $ glSecondaryColor3iEXT r g b secondaryColor3v = liftIO . glSecondaryColor3ivEXT -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glColor3f" glColor3f :: GLfloat -> GLfloat -> GLfloat -> IO () foreign import CALLCONV unsafe "glColor4f" glColor4f :: GLfloat -> GLfloat -> GLfloat -> GLfloat -> IO () foreign import CALLCONV unsafe "glColor3fv" glColor3fv :: Ptr GLfloat -> IO () foreign import CALLCONV unsafe "glColor4fv" glColor4fv :: Ptr GLfloat -> IO () EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3fEXT,GLfloat -> GLfloat -> GLfloat -> IO ()) EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3fvEXT,Ptr GLfloat -> IO ()) instance ColorComponent GLfloat_ where color3 r g b = liftIO $ glColor3f r g b color4 r g b a = liftIO $ glColor4f r g b a color3v = liftIO . glColor3fv color4v = liftIO . glColor4fv secondaryColor3 r g b = liftIO $ glSecondaryColor3fEXT r g b secondaryColor3v = liftIO . glSecondaryColor3fvEXT -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glColor3d" glColor3d :: GLdouble -> GLdouble -> GLdouble -> IO () foreign import CALLCONV unsafe "glColor4d" glColor4d :: GLdouble -> GLdouble -> GLdouble -> GLdouble -> IO () foreign import CALLCONV unsafe "glColor3dv" glColor3dv :: Ptr GLdouble -> IO () foreign import CALLCONV unsafe "glColor4dv" glColor4dv :: Ptr GLdouble -> IO () EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3dEXT,GLdouble -> GLdouble -> GLdouble -> IO ()) EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3dvEXT,Ptr GLdouble -> IO ()) instance ColorComponent GLdouble_ where color3 r g b = liftIO $ glColor3d r g b color4 r g b a = liftIO $ glColor4d r g b a color3v = liftIO . glColor3dv color4v = liftIO . glColor4dv secondaryColor3 r g b = liftIO $ glSecondaryColor3dEXT r g b secondaryColor3v = liftIO . glSecondaryColor3dvEXT -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glColor3ub" glColor3ub :: GLubyte -> GLubyte -> GLubyte -> IO () foreign import CALLCONV unsafe "glColor4ub" glColor4ub :: GLubyte -> GLubyte -> GLubyte -> GLubyte -> IO () foreign import CALLCONV unsafe "glColor3ubv" glColor3ubv :: Ptr GLubyte -> IO () foreign import CALLCONV unsafe "glColor4ubv" glColor4ubv :: Ptr GLubyte -> IO () EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3ubEXT,GLubyte -> GLubyte -> GLubyte -> IO ()) EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3ubvEXT,Ptr GLubyte -> IO ()) instance ColorComponent GLubyte_ where color3 r g b = liftIO $ glColor3ub r g b color4 r g b a = liftIO $ glColor4ub r g b a color3v = liftIO . glColor3ubv color4v = liftIO . glColor4ubv secondaryColor3 r g b = liftIO $ glSecondaryColor3ubEXT r g b secondaryColor3v = liftIO . glSecondaryColor3ubvEXT -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glColor3us" glColor3us :: GLushort -> GLushort -> GLushort -> IO () foreign import CALLCONV unsafe "glColor4us" glColor4us :: GLushort -> GLushort -> GLushort -> GLushort -> IO () foreign import CALLCONV unsafe "glColor3usv" glColor3usv :: Ptr GLushort -> IO () foreign import CALLCONV unsafe "glColor4usv" glColor4usv :: Ptr GLushort -> IO () EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3usEXT,GLushort -> GLushort -> GLushort -> IO ()) EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3usvEXT,Ptr GLushort -> IO ()) instance ColorComponent GLushort_ where color3 r g b = liftIO $ glColor3us r g b color4 r g b a = liftIO $ glColor4us r g b a color3v = liftIO . glColor3usv color4v = liftIO . glColor4usv secondaryColor3 r g b = liftIO $ glSecondaryColor3usEXT r g b secondaryColor3v = liftIO . glSecondaryColor3usvEXT -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glColor3ui" glColor3ui :: GLuint -> GLuint -> GLuint -> IO () foreign import CALLCONV unsafe "glColor4ui" glColor4ui :: GLuint -> GLuint -> GLuint -> GLuint -> IO () foreign import CALLCONV unsafe "glColor3uiv" glColor3uiv :: Ptr GLuint -> IO () foreign import CALLCONV unsafe "glColor4uiv" glColor4uiv :: Ptr GLuint -> IO () EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3uiEXT,GLuint -> GLuint -> GLuint -> IO ()) EXTENSION_ENTRY("GL_EXT_secondary_color or OpenGL 1.4",glSecondaryColor3uivEXT,Ptr GLuint -> IO ()) instance ColorComponent GLuint_ where color3 r g b = liftIO $ glColor3ui r g b color4 r g b a = liftIO $ glColor4ui r g b a color3v = liftIO . glColor3uiv color4v = liftIO . glColor4uiv secondaryColor3 r g b = liftIO $ glSecondaryColor3uiEXT r g b secondaryColor3v = liftIO . glSecondaryColor3uivEXT -------------------------------------------------------------------------------- -- | Change the current color. class Color a where color :: MonadGL m => a -> m () colorv :: MonadGL m => Ptr a -> m () -- An RGBA color with /A/=1. data Color3 a = Color3 !a !a !a deriving ( Eq, Ord, Show ) instance ColorComponent a => Color (Color3 a) where color (Color3 r g b) = color3 r g b colorv = color3v . (castPtr :: Ptr (Color3 b) -> Ptr b) instance Storable a => Storable (Color3 a) where sizeOf ~(Color3 r _ _) = 3 * sizeOf r alignment ~(Color3 r _ _) = alignment r peek = peek3 Color3 . castPtr poke ptr (Color3 r g b) = poke3 (castPtr ptr) r g b -- | A fully-fledged RGBA color. data Color4 a = Color4 !a !a !a !a deriving ( Eq, Ord, Show ) instance ColorComponent a => Color (Color4 a) where color (Color4 r g b a) = color4 r g b a colorv = color4v . (castPtr :: Ptr (Color4 b) -> Ptr b) instance Storable a => Storable (Color4 a) where sizeOf ~(Color4 r _ _ _) = 4 * sizeOf r alignment ~(Color4 r _ _ _) = alignment r peek = peek4 Color4 . castPtr poke ptr (Color4 r g b a) = poke4 (castPtr ptr) r g b a -------------------------------------------------------------------------------- -- | Change the current secondary color. class SecondaryColor a where secondaryColor :: MonadGL m => a -> m () secondaryColorv :: MonadGL m => Ptr a -> m () instance ColorComponent a => SecondaryColor (Color3 a) where secondaryColor (Color3 r g b) = secondaryColor3 r g b secondaryColorv = secondaryColor3v . (castPtr :: Ptr (Color3 b) -> Ptr b) -------------------------------------------------------------------------------- -- The current color index. The initial value is 1. Note that this state -- variable is significant only when the GL is in color index mode. currentIndex :: StateVar (Index1 GLint) currentIndex = makeStateVar (getInteger1 Index1 GetCurrentIndex) (runPrimitive . index) -------------------------------------------------------------------------------- -- | The class of all types which can be used as a color index. class IndexComponent a where index1 :: MonadGL m => a -> m () index1v :: MonadGL m => Ptr a -> m () -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glIndexs" glIndexs :: GLshort -> IO () foreign import CALLCONV unsafe "glIndexsv" glIndexsv :: Ptr GLshort -> IO () instance IndexComponent GLshort_ where index1 = liftIO . glIndexs index1v = liftIO . glIndexsv -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glIndexi" glIndexi :: GLint -> IO () foreign import CALLCONV unsafe "glIndexiv" glIndexiv :: Ptr GLint -> IO () instance IndexComponent GLint_ where index1 = liftIO . glIndexi index1v = liftIO . glIndexiv -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glIndexf" glIndexf :: GLfloat -> IO () foreign import CALLCONV unsafe "glIndexfv" glIndexfv :: Ptr GLfloat -> IO () instance IndexComponent GLfloat_ where index1 = liftIO . glIndexf index1v = liftIO . glIndexfv -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glIndexd" glIndexd :: GLdouble -> IO () foreign import CALLCONV unsafe "glIndexdv" glIndexdv :: Ptr GLdouble -> IO () instance IndexComponent GLdouble_ where index1 = liftIO . glIndexd index1v = liftIO . glIndexdv -------------------------------------------------------------------------------- foreign import CALLCONV unsafe "glIndexub" glIndexub :: GLubyte -> IO () foreign import CALLCONV unsafe "glIndexubv" glIndexubv :: Ptr GLubyte -> IO () instance IndexComponent GLubyte_ where index1 = liftIO . glIndexub index1v = liftIO . glIndexubv -------------------------------------------------------------------------------- -- | Change the current color index. class Index a where index :: MonadGL m => a -> m () -- Collision with Prelude.index indexv :: MonadGL m => Ptr a -> m () -- | A color index. newtype Index1 a = Index1 a deriving ( Eq, Ord, Show ) instance IndexComponent a => Index (Index1 a) where index (Index1 i) = index1 i indexv = index1v . (castPtr :: Ptr (Index1 b) -> Ptr b) instance Storable a => Storable (Index1 a) where sizeOf ~(Index1 s) = sizeOf s alignment ~(Index1 s) = alignment s peek = peek1 Index1 . castPtr poke ptr (Index1 s) = poke1 (castPtr ptr) s -------------------------------------------------------------------------------- newtype AttribLocation = AttribLocation GLuint deriving ( Eq, Ord, Show ) -------------------------------------------------------------------------------- -- | The class of all types which can be used as a generic vertex attribute. class VertexAttribComponent a where vertexAttrib1 :: AttribLocation -> a -> PrimitiveGL () vertexAttrib2 :: AttribLocation -> a -> a -> PrimitiveGL () vertexAttrib3 :: AttribLocation -> a -> a -> a -> PrimitiveGL () vertexAttrib4 :: AttribLocation -> a -> a -> a -> a -> PrimitiveGL () vertexAttrib1v :: AttribLocation -> Ptr a -> PrimitiveGL () vertexAttrib2v :: AttribLocation -> Ptr a -> PrimitiveGL () vertexAttrib3v :: AttribLocation -> Ptr a -> PrimitiveGL () vertexAttrib4v :: AttribLocation -> Ptr a -> PrimitiveGL () -------------------------------------------------------------------------------- EXTENSION_ENTRY("OpenGL 2.0",glGetVertexAttribdv,GLuint -> GLenum -> Ptr GLdouble -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glGetVertexAttribfv,GLuint -> GLenum -> Ptr GLfloat -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glGetVertexAttribiv,GLuint -> GLenum -> Ptr GLint -> PrimitiveGL ()) -------------------------------------------------------------------------------- EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib1s,AttribLocation -> GLshort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib2s,AttribLocation -> GLshort -> GLshort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib3s,AttribLocation -> GLshort -> GLshort -> GLshort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4s,AttribLocation -> GLshort -> GLshort -> GLshort -> GLshort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib1sv,AttribLocation -> Ptr GLshort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib2sv,AttribLocation -> Ptr GLshort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib3sv,AttribLocation -> Ptr GLshort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4sv,AttribLocation -> Ptr GLshort -> PrimitiveGL ()) instance VertexAttribComponent GLshort_ where vertexAttrib1 = glVertexAttrib1s vertexAttrib2 = glVertexAttrib2s vertexAttrib3 = glVertexAttrib3s vertexAttrib4 = glVertexAttrib4s vertexAttrib1v = glVertexAttrib1sv vertexAttrib2v = glVertexAttrib2sv vertexAttrib3v = glVertexAttrib3sv vertexAttrib4v = glVertexAttrib4sv -------------------------------------------------------------------------------- EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib1f,AttribLocation -> GLfloat -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib2f,AttribLocation -> GLfloat -> GLfloat -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib3f,AttribLocation -> GLfloat -> GLfloat -> GLfloat -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4f,AttribLocation -> GLfloat -> GLfloat -> GLfloat -> GLfloat -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib1fv,AttribLocation -> Ptr GLfloat -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib2fv,AttribLocation -> Ptr GLfloat -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib3fv,AttribLocation -> Ptr GLfloat -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4fv,AttribLocation -> Ptr GLfloat -> PrimitiveGL ()) instance VertexAttribComponent GLfloat_ where vertexAttrib1 = glVertexAttrib1f vertexAttrib2 = glVertexAttrib2f vertexAttrib3 = glVertexAttrib3f vertexAttrib4 = glVertexAttrib4f vertexAttrib1v = glVertexAttrib1fv vertexAttrib2v = glVertexAttrib2fv vertexAttrib3v = glVertexAttrib3fv vertexAttrib4v = glVertexAttrib4fv -------------------------------------------------------------------------------- EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib1d,AttribLocation -> GLdouble -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib2d,AttribLocation -> GLdouble -> GLdouble -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib3d,AttribLocation -> GLdouble -> GLdouble -> GLdouble -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4d,AttribLocation -> GLdouble -> GLdouble -> GLdouble -> GLdouble -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib1dv,AttribLocation -> Ptr GLdouble -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib2dv,AttribLocation -> Ptr GLdouble -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib3dv,AttribLocation -> Ptr GLdouble -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4dv,AttribLocation -> Ptr GLdouble -> PrimitiveGL ()) instance VertexAttribComponent GLdouble_ where vertexAttrib1 = glVertexAttrib1d vertexAttrib2 = glVertexAttrib2d vertexAttrib3 = glVertexAttrib3d vertexAttrib4 = glVertexAttrib4d vertexAttrib1v = glVertexAttrib1dv vertexAttrib2v = glVertexAttrib2dv vertexAttrib3v = glVertexAttrib3dv vertexAttrib4v = glVertexAttrib4dv -------------------------------------------------------------------------------- EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4bv,AttribLocation -> Ptr GLbyte -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4ubv,AttribLocation -> Ptr GLubyte -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4usv,AttribLocation -> Ptr GLushort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4iv,AttribLocation -> Ptr GLint -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4uiv,AttribLocation -> Ptr GLuint -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4Nbv,AttribLocation -> Ptr GLbyte -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4Nubv,AttribLocation -> Ptr GLubyte -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4Nusv,AttribLocation -> Ptr GLushort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4Niv,AttribLocation -> Ptr GLint -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4Nuiv,AttribLocation -> Ptr GLuint -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4Nsv,AttribLocation -> Ptr GLshort -> PrimitiveGL ()) EXTENSION_ENTRY("OpenGL 2.0",glVertexAttrib4Nub,AttribLocation -> GLubyte -> GLubyte -> GLubyte -> GLubyte -> PrimitiveGL ()) -------------------------------------------------------------------------------- class VertexAttrib a where vertexAttrib :: AttribLocation -> a -> PrimitiveGL () vertexAttribv :: AttribLocation -> Ptr a -> PrimitiveGL () instance VertexAttribComponent a => VertexAttrib (Vertex2 a) where vertexAttrib location (Vertex2 x y) = vertexAttrib2 location x y vertexAttribv location = vertexAttrib2v location . (castPtr :: Ptr (Vertex2 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (Vertex3 a) where vertexAttrib location (Vertex3 x y z) = vertexAttrib3 location x y z vertexAttribv location = vertexAttrib3v location . (castPtr :: Ptr (Vertex3 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (Vertex4 a) where vertexAttrib location (Vertex4 x y z w) = vertexAttrib4 location x y z w vertexAttribv location = vertexAttrib4v location . (castPtr :: Ptr (Vertex4 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (TexCoord1 a) where vertexAttrib location (TexCoord1 s) = vertexAttrib1 location s vertexAttribv location = vertexAttrib1v location . (castPtr :: Ptr (TexCoord1 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (TexCoord2 a) where vertexAttrib location (TexCoord2 s t) = vertexAttrib2 location s t vertexAttribv location = vertexAttrib2v location . (castPtr :: Ptr (TexCoord2 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (TexCoord3 a) where vertexAttrib location (TexCoord3 s t u) = vertexAttrib3 location s t u vertexAttribv location = vertexAttrib3v location . (castPtr :: Ptr (TexCoord3 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (TexCoord4 a) where vertexAttrib location (TexCoord4 s t u v) = vertexAttrib4 location s t u v vertexAttribv location = vertexAttrib4v location . (castPtr :: Ptr (TexCoord4 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (Normal3 a) where vertexAttrib location (Normal3 x y z) = vertexAttrib3 location x y z vertexAttribv location = vertexAttrib3v location . (castPtr :: Ptr (Normal3 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (FogCoord1 a) where vertexAttrib location (FogCoord1 c) = vertexAttrib1 location c vertexAttribv location = vertexAttrib1v location . (castPtr :: Ptr (FogCoord1 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (Color3 a) where vertexAttrib location (Color3 r g b) = vertexAttrib3 location r g b vertexAttribv location = vertexAttrib3v location . (castPtr :: Ptr (Color3 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (Color4 a) where vertexAttrib location (Color4 r g b a) = vertexAttrib4 location r g b a vertexAttribv location = vertexAttrib4v location . (castPtr :: Ptr (Color4 b) -> Ptr b) instance VertexAttribComponent a => VertexAttrib (Index1 a) where vertexAttrib location (Index1 i) = vertexAttrib1 location i vertexAttribv location = vertexAttrib1v location . (castPtr :: Ptr (Index1 b) -> Ptr b) -------------------------------------------------------------------------------- -- | An implementation must support at least 2 texture units, but it may -- support up to 32 ones. This state variable can be used to query the actual -- implementation limit. maxTextureUnit :: GettableStateVar TextureUnit maxTextureUnit = makeGettableStateVar (getEnum1 unmarshalTextureUnit GetMaxTextureUnits)