GPipe-2.1.5: Typesafe functional GPU graphics programming

Safe HaskellNone
LanguageHaskell98

Graphics.GPipe.PrimitiveStream

Contents

Description

A PrimitiveArray can be turned into a PrimitiveStream in a Shader, in order to operate on the vertices of it and ultimately rasterize it into a FragmentStream.

Synopsis

The data type

data PrimitiveStream t a Source

A PrimitiveStream t a is a stream of primitives of type t where the vertices are values of type a. You can operate a stream's vertex values using the Functor instance (this will result in a shader running on the GPU). You may also append PrimitiveStreams using the Monoid instance, but if possible append the origin PrimitiveArrays instead, as this will create more optimized draw calls.

class BufferFormat a => VertexInput a where Source

This class constraints which buffer types can be turned into vertex values, and what type those values have.

Associated Types

type VertexFormat a Source

The type the buffer value will be turned into once it becomes a vertex value.

Methods

toVertex :: ToVertex a (VertexFormat a) Source

An arrow action that turns a value from it's buffer representation to it's vertex representation. Use toVertex from the GPipe provided instances to operate in this arrow. Also note that this arrow needs to be able to return a value lazily, so ensure you use

proc ~pattern -> do ....

Instances

VertexInput () Source 
VertexInput a => VertexInput (V0 a) Source 
VertexInput a => VertexInput (V1 a) Source 
VertexInput a => VertexInput (V2 a) Source 
VertexInput a => VertexInput (V3 a) Source 
VertexInput a => VertexInput (V4 a) Source 
VertexInput a => VertexInput (Plucker a) Source 
VertexInput a => VertexInput (Quaternion a) Source 
VertexInput (Normalized (B4 Int8)) Source 
VertexInput (Normalized (B4 Int16)) Source 
VertexInput (Normalized (B4 Int32)) Source 
VertexInput (Normalized (B4 Word8)) Source 
VertexInput (Normalized (B4 Word16)) Source 
VertexInput (Normalized (B4 Word32)) Source 
VertexInput (Normalized (B3 Int8)) Source 
VertexInput (Normalized (B3 Int16)) Source 
VertexInput (Normalized (B3 Int32)) Source 
VertexInput (Normalized (B3 Word8)) Source 
VertexInput (Normalized (B3 Word16)) Source 
VertexInput (Normalized (B3 Word32)) Source 
VertexInput (Normalized (B2 Int16)) Source 
VertexInput (Normalized (B2 Int32)) Source 
VertexInput (Normalized (B2 Word16)) Source 
VertexInput (Normalized (B2 Word32)) Source 
VertexInput (Normalized (B Int32)) Source 
VertexInput (Normalized (B Word32)) Source 
VertexInput (B4 Float) Source 
VertexInput (B4 Int8) Source 
VertexInput (B4 Int16) Source 
VertexInput (B4 Int32) Source 
VertexInput (B4 Word8) Source 
VertexInput (B4 Word16) Source 
VertexInput (B4 Word32) Source 
VertexInput (B3 Float) Source 
VertexInput (B3 Int8) Source 
VertexInput (B3 Int16) Source 
VertexInput (B3 Int32) Source 
VertexInput (B3 Word8) Source 
VertexInput (B3 Word16) Source 
VertexInput (B3 Word32) Source 
VertexInput (B2 Float) Source 
VertexInput (B2 Int16) Source 
VertexInput (B2 Int32) Source 
VertexInput (B2 Word16) Source 
VertexInput (B2 Word32) Source 
VertexInput (B Float) Source 
VertexInput (B Int32) Source 
VertexInput (B Word32) Source 
(VertexInput a, VertexInput b) => VertexInput (a, b) Source 
(VertexInput (f a), VertexInput a, (~) * (HostFormat (f a)) (f (HostFormat a)), (~) * (VertexFormat (f a)) (f (VertexFormat a))) => VertexInput (Point f a) Source 
(VertexInput a, VertexInput b, VertexInput c) => VertexInput (a, b, c) Source 
(VertexInput a, VertexInput b, VertexInput c, VertexInput d) => VertexInput (a, b, c, d) Source 
(VertexInput a, VertexInput b, VertexInput c, VertexInput d, VertexInput e) => VertexInput (a, b, c, d, e) Source 
(VertexInput a, VertexInput b, VertexInput c, VertexInput d, VertexInput e, VertexInput f) => VertexInput (a, b, c, d, e, f) Source 
(VertexInput a, VertexInput b, VertexInput c, VertexInput d, VertexInput e, VertexInput f, VertexInput g) => VertexInput (a, b, c, d, e, f, g) Source 

data ToVertex a b Source

The arrow type for toVertex.

Creating PrimitiveStreams

toPrimitiveStream :: forall os f s a p. VertexInput a => (s -> PrimitiveArray p a) -> Shader os f s (PrimitiveStream p (VertexFormat a)) Source

Create a primitive stream from a primitive array provided from the shader environment.

Various PrimitiveStream operations

withInputIndices :: (a -> InputIndices -> b) -> PrimitiveStream p a -> PrimitiveStream p b Source

Like fmap, but where the vertex and instance IDs are provided as arguments as well.

withPointSize :: (a -> PointSize -> (b, PointSize)) -> PrimitiveStream Points a -> PrimitiveStream Points b Source

Like fmap, but where each point's size is provided as arguments as well, and a new point size is set for each point in addition to the new vertex value.

When a PrimitiveStream of Points is created, all points will have the default size of 1.