GPipe-Core-0.2.3.2: Typesafe functional GPU graphics programming
Safe HaskellNone
LanguageHaskell2010

Graphics.GPipe.Internal.PrimitiveArray

Synopsis

Documentation

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.

Constructors

VertexArray 

Fields

Instances

Instances details
Functor (VertexArray t) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveArray

Methods

fmap :: (a -> b) -> VertexArray t a -> VertexArray t b #

(<$) :: a -> VertexArray t b -> VertexArray t a #

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 (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.

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.

type family Combine t t' where ... Source #

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.

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.

Constructors

IndexArray 

Fields

newIndexArray :: forall os f b a. (BufferFormat b, Integral a, IndexFormat b ~ a) => Buffer os b -> Maybe a -> Render os 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.

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.

class PrimitiveTopology p where Source #

Associated Types

data Geometry p a Source #

Instances

Instances details
PrimitiveTopology TrianglesWithAdjacency Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveArray

Associated Types

data Geometry TrianglesWithAdjacency a Source #

PrimitiveTopology Triangles Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveArray

Associated Types

data Geometry Triangles a Source #

PrimitiveTopology LinesWithAdjacency Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveArray

Associated Types

data Geometry LinesWithAdjacency a Source #

PrimitiveTopology Lines Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveArray

Associated Types

data Geometry Lines a Source #

PrimitiveTopology Points Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveArray

Associated Types

data Geometry Points a Source #

newtype PrimitiveArray p a Source #

An array of primitives

Constructors

PrimitiveArray 

Instances

Instances details
Functor (PrimitiveArray p) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveArray

Methods

fmap :: (a -> b) -> PrimitiveArray p a -> PrimitiveArray p b #

(<$) :: a -> PrimitiveArray p b -> PrimitiveArray p a #

Semigroup (PrimitiveArray p a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveArray

Monoid (PrimitiveArray p a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.PrimitiveArray