GPipe-2.1.5: Typesafe functional GPU graphics programming

Safe HaskellNone
LanguageHaskell98

Graphics.GPipe.PrimitiveArray

Contents

Description

PrimitiveArrays (aka VAOs in OpenGl) are the main input to compiled shaders. A primitive array is created from one or more zipped vertex arrays. A primitive array may also be instanced, using one or more zipped vertex arrays as instance arrays. And lastly, an index array may also be used to pick vertices for the primitive array.

Any possible combination of interleaved or non-interleaved vertex buffers may be used, for example:

Buffer a = {(A,B),(A,B),(A,B)...} Buffer b = {(X,Y,Z),(X,Y,Z),(X,Y,Z),...}

  do
     aArr <- newVertexArray a        
     bArr <- newVertexArray b 
     let primArr = toPrimitiveArray TriangleList (zipVertices ((a,b) y -> (a,b,y)) aArr (fmap ((_,y,_) -> y) bArr))
 

will create a primitive array primArr with this layout: {(A,B,Y),(A,B,Y),(A,B,Y)...}

Synopsis

Vertex arrays

data VertexArray t a Source

A vertex array is the basic building block for a primitive array. It is created from the contents of a Buffer, but unlike a Buffer, it may be truncated, zipped with other vertex arrays, and even morphed into arrays of a different type with the provided Functor instance. A VertexArray t a has elements of type a, and t indicates whether the vertex array may be used as instances or not.

Instances

data Instances Source

A phantom type to indicate that a VertexArray may only be used for instances (in toPrimitiveArrayInstanced and toPrimitiveArrayIndexedInstanced).

newVertexArray :: Buffer os a -> Render os f (VertexArray t a) Source

Create a VertexArray from a Buffer. The vertex array will have the same number of elements as the buffer, use takeVertices and dropVertices to make it smaller.

vertexArrayLength :: VertexArray t a -> Int Source

Retrieve the number of elements in a VertexArray.

zipVertices :: (a -> b -> c) -> VertexArray t a -> VertexArray t' b -> VertexArray (Combine t t') c Source

Zip two VertexArrays using the function given as first argument. If either of the argument VertexArrays are restriced to Instances only, then so will the resulting array be, as depicted by the Combine type family.

takeVertices :: Int -> VertexArray t a -> VertexArray t a Source

takeVertices n a creates a shorter vertex array by taking the n first elements of the array a.

dropVertices :: Int -> VertexArray () a -> VertexArray t a Source

dropVertices n a creates a shorter vertex array by dropping the n first elements of the array a. The argument array a must not be constrained to only Instances.

replicateEach :: Int -> VertexArray t a -> VertexArray Instances a Source

replicateEach n a will create a longer vertex array, only to be used for instances, by replicating each element of the array a n times. E.g. replicateEach 3 {ABCD...} will yield {AAABBBCCCDDD...}. This is particulary useful before zipping the array with another that has a different replication rate.

Index arrays

data IndexArray Source

An index array is like a vertex array, but contains only integer indices. These indices must come from a tightly packed Buffer, hence the lack of a Functor instance and no conversion from VertexArrays.

newIndexArray :: forall os f b a. (BufferFormat b, Integral a, IndexFormat b ~ a) => Buffer os b -> Maybe a -> Render os f IndexArray Source

Create an IndexArray from a Buffer of unsigned integers (as constrained by the closed IndexFormat type family instances). The index array will have the same number of elements as the buffer, use takeIndices and dropIndices to make it smaller. The Maybe a argument is used to optionally denote a primitive restart index.

indexArrayLength :: IndexArray -> Int Source

Numer of indices in an IndexArray.

takeIndices :: Int -> IndexArray -> IndexArray Source

takeIndices n a creates a shorter index array by taking the n first indices of the array a.

dropIndices :: Int -> IndexArray -> IndexArray Source

dropIndices n a creates a shorter index array by dropping the n first indices of the array a.

Primitive arrays

data PrimitiveArray p a Source

An array of primitives

Operations on buffer values

You may split up a B4 a, B3 a and B2 a value into its components, if the parts are representable buffer types (e.g. due to alignment, you may for instance not split a B4 Word8). Note that there are no functions to combine smaller parts together again.

toB22 :: forall a. (Storable a, BufferFormat (B2 a)) => B4 a -> (B2 a, B2 a) Source

Split up a B4 a into two B2 as.

toB3 :: forall a. (Storable a, BufferFormat (B3 a)) => B4 a -> B3 a Source

Discard the last component of a B4 a to get a B3 a.

toB21 :: forall a. (Storable a, BufferFormat (B a)) => B3 a -> (B2 a, B a) Source

Split up a B3 a into a B2 a and a B1 a.

toB12 :: forall a. (Storable a, BufferFormat (B a)) => B3 a -> (B a, B2 a) Source

Split up a B3 a into a B1 a and a B2 a.

toB11 :: forall a. (Storable a, BufferFormat (B a)) => B2 a -> (B a, B a) Source

Split up a B2 a into two B1 as.