| Copyright | (c) Sven Panne 2002-2019 | 
|---|---|
| License | BSD3 | 
| Maintainer | Sven Panne <svenpanne@gmail.com> | 
| Stability | stable | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Graphics.Rendering.OpenGL.GL.VertexArrays
Contents
Description
This module corresponds to section 2.8 (Vertex Arrays) of the OpenGL 2.1 specs.
Synopsis
- type NumComponents = GLint
- data DataType- = UnsignedByte
- | Byte
- | UnsignedShort
- | Short
- | UnsignedInt
- | Int
- | HalfFloat
- | Float
- | UnsignedByte332
- | UnsignedByte233Rev
- | UnsignedShort565
- | UnsignedShort565Rev
- | UnsignedShort4444
- | UnsignedShort4444Rev
- | UnsignedShort5551
- | UnsignedShort1555Rev
- | UnsignedInt8888
- | UnsignedInt8888Rev
- | UnsignedInt1010102
- | UnsignedInt2101010Rev
- | UnsignedInt248
- | UnsignedInt10f11f11fRev
- | UnsignedInt5999Rev
- | Float32UnsignedInt248Rev
- | Bitmap
- | UnsignedShort88
- | UnsignedShort88Rev
- | Double
- | TwoBytes
- | ThreeBytes
- | FourBytes
 
- type Stride = GLsizei
- data VertexArrayDescriptor a = VertexArrayDescriptor !NumComponents !DataType !Stride !(Ptr a)
- data Capability
- data ClientArrayType
- arrayPointer :: ClientArrayType -> StateVar (VertexArrayDescriptor a)
- data InterleavedArrays- = V2f
- | V3f
- | C4ubV2f
- | C4ubV3f
- | C3fV3f
- | N3fV3f
- | C4fN3fV3f
- | T2fV3f
- | T4fV4f
- | T2fC4ubV3f
- | T2fC3fV3f
- | T2fN3fV3f
- | T2fC4fN3fV3f
- | T4fC4fN3fV4f
 
- interleavedArrays :: InterleavedArrays -> Stride -> Ptr a -> IO ()
- clientState :: ClientArrayType -> StateVar Capability
- clientActiveTexture :: StateVar TextureUnit
- type ArrayIndex = GLint
- type NumArrayIndices = GLsizei
- type NumIndexBlocks = GLsizei
- type NumInstances = GLsizei
- type BaseInstance = GLuint
- type BaseVertex = GLint
- arrayElement :: ArrayIndex -> IO ()
- drawArrays :: PrimitiveMode -> ArrayIndex -> NumArrayIndices -> IO ()
- drawArraysInstancedBaseInstance :: PrimitiveMode -> ArrayIndex -> NumArrayIndices -> NumInstances -> BaseInstance -> IO ()
- drawArraysInstanced :: PrimitiveMode -> ArrayIndex -> NumArrayIndices -> NumInstances -> IO ()
- multiDrawArrays :: PrimitiveMode -> Ptr ArrayIndex -> Ptr NumArrayIndices -> NumIndexBlocks -> IO ()
- drawElements :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> IO ()
- drawElementsInstancedBaseInstance :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> NumInstances -> BaseInstance -> IO ()
- drawElementsInstanced :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> NumInstances -> IO ()
- multiDrawElements :: PrimitiveMode -> Ptr NumArrayIndices -> DataType -> Ptr (Ptr a) -> NumIndexBlocks -> IO ()
- drawRangeElements :: PrimitiveMode -> (ArrayIndex, ArrayIndex) -> NumArrayIndices -> DataType -> Ptr a -> IO ()
- drawElementsBaseVertex :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> BaseVertex -> IO ()
- drawRangeElementsBaseVertex :: PrimitiveMode -> (ArrayIndex, ArrayIndex) -> NumArrayIndices -> DataType -> Ptr a -> BaseVertex -> IO ()
- drawElementsInstancedBaseVertex :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> NumInstances -> BaseVertex -> IO ()
- drawElementsInstancedBaseVertexBaseInstance :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> NumInstances -> BaseVertex -> BaseInstance -> IO ()
- multiDrawElementsBaseVertex :: PrimitiveMode -> Ptr NumArrayIndices -> DataType -> Ptr (Ptr a) -> NumIndexBlocks -> Ptr BaseVertex -> IO ()
- maxElementsVertices :: GettableStateVar NumArrayIndices
- maxElementsIndices :: GettableStateVar NumArrayIndices
- lockArrays :: StateVar (Maybe (ArrayIndex, NumArrayIndices))
- primitiveRestartIndex :: StateVar (Maybe ArrayIndex)
- primitiveRestartIndexNV :: StateVar (Maybe ArrayIndex)
- vertexAttribPointer :: AttribLocation -> StateVar (IntegerHandling, VertexArrayDescriptor a)
- vertexAttribArray :: AttribLocation -> StateVar Capability
Describing Data for the Arrays
type NumComponents = GLint Source #
Constructors
data VertexArrayDescriptor a Source #
Constructors
| VertexArrayDescriptor !NumComponents !DataType !Stride !(Ptr a) | 
Instances
Specifying Data for the Arrays
data Capability Source #
Instances
| Eq Capability Source # | |
| Defined in Graphics.Rendering.OpenGL.GL.Capability | |
| Ord Capability Source # | |
| Defined in Graphics.Rendering.OpenGL.GL.Capability Methods compare :: Capability -> Capability -> Ordering # (<) :: Capability -> Capability -> Bool # (<=) :: Capability -> Capability -> Bool # (>) :: Capability -> Capability -> Bool # (>=) :: Capability -> Capability -> Bool # max :: Capability -> Capability -> Capability # min :: Capability -> Capability -> Capability # | |
| Show Capability Source # | |
| Defined in Graphics.Rendering.OpenGL.GL.Capability Methods showsPrec :: Int -> Capability -> ShowS # show :: Capability -> String # showList :: [Capability] -> ShowS # | |
data ClientArrayType Source #
Constructors
| VertexArray | |
| NormalArray | |
| ColorArray | |
| IndexArray | |
| TextureCoordArray | |
| EdgeFlagArray | |
| FogCoordArray | |
| SecondaryColorArray | |
| MatrixIndexArray | 
Instances
| Eq ClientArrayType Source # | |
| Defined in Graphics.Rendering.OpenGL.GL.VertexArrays Methods (==) :: ClientArrayType -> ClientArrayType -> Bool # (/=) :: ClientArrayType -> ClientArrayType -> Bool # | |
| Ord ClientArrayType Source # | |
| Defined in Graphics.Rendering.OpenGL.GL.VertexArrays Methods compare :: ClientArrayType -> ClientArrayType -> Ordering # (<) :: ClientArrayType -> ClientArrayType -> Bool # (<=) :: ClientArrayType -> ClientArrayType -> Bool # (>) :: ClientArrayType -> ClientArrayType -> Bool # (>=) :: ClientArrayType -> ClientArrayType -> Bool # max :: ClientArrayType -> ClientArrayType -> ClientArrayType # min :: ClientArrayType -> ClientArrayType -> ClientArrayType # | |
| Show ClientArrayType Source # | |
| Defined in Graphics.Rendering.OpenGL.GL.VertexArrays Methods showsPrec :: Int -> ClientArrayType -> ShowS # show :: ClientArrayType -> String # showList :: [ClientArrayType] -> ShowS # | |
data InterleavedArrays Source #
Constructors
| V2f | |
| V3f | |
| C4ubV2f | |
| C4ubV3f | |
| C3fV3f | |
| N3fV3f | |
| C4fN3fV3f | |
| T2fV3f | |
| T4fV4f | |
| T2fC4ubV3f | |
| T2fC3fV3f | |
| T2fN3fV3f | |
| T2fC4fN3fV3f | |
| T4fC4fN3fV4f | 
Instances
| Eq InterleavedArrays Source # | |
| Defined in Graphics.Rendering.OpenGL.GL.VertexArrays Methods (==) :: InterleavedArrays -> InterleavedArrays -> Bool # (/=) :: InterleavedArrays -> InterleavedArrays -> Bool # | |
| Ord InterleavedArrays Source # | |
| Defined in Graphics.Rendering.OpenGL.GL.VertexArrays Methods compare :: InterleavedArrays -> InterleavedArrays -> Ordering # (<) :: InterleavedArrays -> InterleavedArrays -> Bool # (<=) :: InterleavedArrays -> InterleavedArrays -> Bool # (>) :: InterleavedArrays -> InterleavedArrays -> Bool # (>=) :: InterleavedArrays -> InterleavedArrays -> Bool # max :: InterleavedArrays -> InterleavedArrays -> InterleavedArrays # min :: InterleavedArrays -> InterleavedArrays -> InterleavedArrays # | |
| Show InterleavedArrays Source # | |
| Defined in Graphics.Rendering.OpenGL.GL.VertexArrays Methods showsPrec :: Int -> InterleavedArrays -> ShowS # show :: InterleavedArrays -> String # showList :: [InterleavedArrays] -> ShowS # | |
interleavedArrays :: InterleavedArrays -> Stride -> Ptr a -> IO () Source #
Enabling Arrays
Dereferencing and Rendering
type ArrayIndex = GLint Source #
type NumArrayIndices = GLsizei Source #
type NumIndexBlocks = GLsizei Source #
type NumInstances = GLsizei Source #
type BaseInstance = GLuint Source #
type BaseVertex = GLint Source #
arrayElement :: ArrayIndex -> IO () Source #
drawArrays :: PrimitiveMode -> ArrayIndex -> NumArrayIndices -> IO () Source #
drawArraysInstancedBaseInstance :: PrimitiveMode -> ArrayIndex -> NumArrayIndices -> NumInstances -> BaseInstance -> IO () Source #
drawArraysInstanced :: PrimitiveMode -> ArrayIndex -> NumArrayIndices -> NumInstances -> IO () Source #
multiDrawArrays :: PrimitiveMode -> Ptr ArrayIndex -> Ptr NumArrayIndices -> NumIndexBlocks -> IO () Source #
drawElements :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> IO () Source #
drawElementsInstancedBaseInstance :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> NumInstances -> BaseInstance -> IO () Source #
drawElementsInstanced :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> NumInstances -> IO () Source #
multiDrawElements :: PrimitiveMode -> Ptr NumArrayIndices -> DataType -> Ptr (Ptr a) -> NumIndexBlocks -> IO () Source #
drawRangeElements :: PrimitiveMode -> (ArrayIndex, ArrayIndex) -> NumArrayIndices -> DataType -> Ptr a -> IO () Source #
drawElementsBaseVertex :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> BaseVertex -> IO () Source #
drawRangeElementsBaseVertex :: PrimitiveMode -> (ArrayIndex, ArrayIndex) -> NumArrayIndices -> DataType -> Ptr a -> BaseVertex -> IO () Source #
drawElementsInstancedBaseVertex :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> NumInstances -> BaseVertex -> IO () Source #
drawElementsInstancedBaseVertexBaseInstance :: PrimitiveMode -> NumArrayIndices -> DataType -> Ptr a -> NumInstances -> BaseVertex -> BaseInstance -> IO () Source #
multiDrawElementsBaseVertex :: PrimitiveMode -> Ptr NumArrayIndices -> DataType -> Ptr (Ptr a) -> NumIndexBlocks -> Ptr BaseVertex -> IO () Source #
lockArrays :: StateVar (Maybe (ArrayIndex, NumArrayIndices)) Source #