GPipe-2.1.5: Typesafe functional GPU graphics programming

Safe HaskellNone
LanguageHaskell98

Graphics.GPipe.Buffer

Contents

Description

Buffers are arrays of data that resides on the GPU. A buffer is strongly typed with an immutable size, but it's content is mutable. A buffer lives in an object space and may be shared between contexts.

Buffers in GPipe are used to store vertices, indices and uniform values and can also be used to copy pixel data to and from textures. They can be written from the host (ie the normal Haskell world) but cannot be read back (but textures can).

The atomic buffer element types are B a, B2 a, B3 a and B4 a where a is a normal haskell type such as Int32 or Float. By creating instances of the type class BufferFormat you may create new composite buffer types.

Synopsis

Buffer data type

data Buffer os b Source

A Buffer os b lives in the object space os and contains elements of type b.

Instances

Eq (Buffer os b) Source 

class BufferFormat f where Source

The class that constraints which types can live in a buffer.

Associated Types

type HostFormat f Source

The type a value of this format has when it lives on the host (i.e. normal Haskell world)

Methods

toBuffer :: ToBuffer (HostFormat f) f Source

An arrow action that turns a value from it's host representation to it's buffer representation. Use toBuffer 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

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

data ToBuffer a b Source

The arrow type for toBuffer.

Atomic buffer types

These types represent primitive host values such as Float and Int32 in a buffer. B2 a, B3 a and B4 a represent vectors of 2, 3 and 4 values of host type a. You cannot do anything special with values of these lifted types (like add two B Floats), only convert it into something useful later, e.g. in a PrimitiveStream.

Since vertex arrays have to be 4 byte aligned, only combinations that add up to a multiple of 4 byte is provided (except for some instances of B3 a which will be automatically padded when necessary).

data B2 a Source

An atomic buffer value that represents a vector of 2 as on the host.

data B3 a Source

An atomic buffer value that represents a vector of 3 as on the host.

Instances

BufferFormat (B3 Float) Source 
BufferFormat (B3 Int8) Source 
BufferFormat (B3 Int16) Source 
BufferFormat (B3 Int32) Source 
BufferFormat (B3 Word8) Source 
BufferFormat (B3 Word16) Source 
BufferFormat (B3 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 (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 
UniformInput (B3 Float) Source 
UniformInput (B3 Int32) Source 
UniformInput (B3 Word32) Source 
type HostFormat (B3 Float) = V3 Float Source 
type HostFormat (B3 Int8) = V3 Int8 Source 
type HostFormat (B3 Int16) = V3 Int16 Source 
type HostFormat (B3 Int32) = V3 Int32 Source 
type HostFormat (B3 Word8) = V3 Word8 Source 
type HostFormat (B3 Word16) = V3 Word16 Source 
type HostFormat (B3 Word32) = V3 Word32 Source 
type VertexFormat (Normalized (B3 Int8)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Int16)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Int32)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Word8)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Word16)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Word32)) = V3 VFloat Source 
type VertexFormat (B3 Float) = V3 VFloat Source 
type VertexFormat (B3 Int8) = V3 VInt Source 
type VertexFormat (B3 Int16) = V3 VInt Source 
type VertexFormat (B3 Int32) = V3 VInt Source 
type VertexFormat (B3 Word8) = V3 VWord Source 
type VertexFormat (B3 Word16) = V3 VWord Source 
type VertexFormat (B3 Word32) = V3 VWord Source 
type UniformFormat (B3 Float) x = V3 (S x Float) Source 
type UniformFormat (B3 Int32) x = V3 (S x Int) Source 
type UniformFormat (B3 Word32) x = V3 (S x Word) Source 

data B4 a Source

An atomic buffer value that represents a vector of 4 as on the host. This works similar to '(B a, B a, B a, B a)' but has some performance advantage, especially when used in VertexArrays.

Instances

BufferFormat (B4 Float) Source 
BufferFormat (B4 Int8) Source 
BufferFormat (B4 Int16) Source 
BufferFormat (B4 Int32) Source 
BufferFormat (B4 Word8) Source 
BufferFormat (B4 Word16) Source 
BufferFormat (B4 Word32) 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 (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 
UniformInput (B4 Float) Source 
UniformInput (B4 Int32) Source 
UniformInput (B4 Word32) Source 
type HostFormat (B4 Float) = V4 Float Source 
type HostFormat (B4 Int8) = V4 Int8 Source 
type HostFormat (B4 Int16) = V4 Int16 Source 
type HostFormat (B4 Int32) = V4 Int32 Source 
type HostFormat (B4 Word8) = V4 Word8 Source 
type HostFormat (B4 Word16) = V4 Word16 Source 
type HostFormat (B4 Word32) = V4 Word32 Source 
type VertexFormat (Normalized (B4 Int8)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Int16)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Int32)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Word8)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Word16)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Word32)) = V4 VFloat Source 
type VertexFormat (B4 Float) = V4 VFloat Source 
type VertexFormat (B4 Int8) = V4 VInt Source 
type VertexFormat (B4 Int16) = V4 VInt Source 
type VertexFormat (B4 Int32) = V4 VInt Source 
type VertexFormat (B4 Word8) = V4 VWord Source 
type VertexFormat (B4 Word16) = V4 VWord Source 
type VertexFormat (B4 Word32) = V4 VWord Source 
type UniformFormat (B4 Float) x = V4 (S x Float) Source 
type UniformFormat (B4 Int32) x = V4 (S x Int) Source 
type UniformFormat (B4 Word32) x = V4 (S x Word) Source 

data BPacked a Source

This works like a 'B a', but has an alignment smaller than 4 bytes that is the limit for vertex buffers, and thus cannot be used for those. Index buffers on the other hand need to be tightly packed, so you need to use this type for index buffers of Word8 or Word16.

newtype Normalized a Source

This wrapper is used for integer values to indicate that it should be interpreted as a floating point value, in the range [-1,1] or [0,1] depending on wether it is a signed or unsigned integer (i.e. Int or Word).

Constructors

Normalized a 

Instances

BufferFormat a => BufferFormat (Normalized 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 
type HostFormat (Normalized a) = HostFormat a Source 
type VertexFormat (Normalized (B4 Int8)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Int16)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Int32)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Word8)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Word16)) = V4 VFloat Source 
type VertexFormat (Normalized (B4 Word32)) = V4 VFloat Source 
type VertexFormat (Normalized (B3 Int8)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Int16)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Int32)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Word8)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Word16)) = V3 VFloat Source 
type VertexFormat (Normalized (B3 Word32)) = V3 VFloat Source 
type VertexFormat (Normalized (B2 Int16)) = V2 VFloat Source 
type VertexFormat (Normalized (B2 Int32)) = V2 VFloat Source 
type VertexFormat (Normalized (B2 Word16)) = V2 VFloat Source 
type VertexFormat (Normalized (B2 Word32)) = V2 VFloat Source 
type VertexFormat (Normalized (B Int32)) = VFloat Source 
type VertexFormat (Normalized (B Word32)) = VFloat Source 

Operating on Buffers

newBuffer :: (MonadIO m, BufferFormat b) => Int -> ContextT w os f m (Buffer os b) Source

Create a buffer with a specified number of elements.

bufferLength :: Buffer os b -> Int Source

Retrieve the number of elements in a buffer.

writeBuffer :: MonadIO m => Buffer os b -> BufferStartPos -> [HostFormat b] -> ContextT w os f m () Source

Write a buffer from the host (i.e. the normal Haskell world).

copyBuffer :: MonadIO m => Buffer os b -> BufferStartPos -> Buffer os b -> BufferStartPos -> Int -> ContextT w os f m () Source

Copies values from one buffer to another (of the same type).

copyBuffer fromBuffer fromStart toBuffer toStart length will copy length elements from position fromStart in fromBuffer to position toStart in toBuffer.

Buffer colors

type family BufferColor c h Source

This type family restricts what host and buffer types a texture format may be converted into. 'BufferColor t h' for a texture representation t and a host representation h will evaluate to a buffer type used in the transfer. This family is closed, i.e. you cannot create additional instances to it.

Equations

BufferColor Float Int32 = Normalized (B Int32) 
BufferColor Float Word32 = Normalized (B Word32) 
BufferColor Float Float = B Float 
BufferColor Int Int32 = B Int32 
BufferColor Word Word32 = B Word32 
BufferColor Word Word16 = BPacked Word16 
BufferColor Word Word8 = BPacked Word8 
BufferColor (V2 Float) (V2 Int32) = Normalized (B2 Int32) 
BufferColor (V2 Float) (V2 Int16) = Normalized (B2 Int16) 
BufferColor (V2 Float) (V2 Word32) = Normalized (B2 Word32) 
BufferColor (V2 Float) (V2 Word16) = Normalized (B2 Word16) 
BufferColor (V2 Float) (V2 Float) = B2 Float 
BufferColor (V2 Int) (V2 Int32) = B2 Int32 
BufferColor (V2 Int) (V2 Int16) = B2 Int16 
BufferColor (V2 Word) (V2 Word32) = B2 Word32 
BufferColor (V2 Word) (V2 Word16) = B2 Word16 
BufferColor (V3 Float) (V3 Int32) = Normalized (B3 Int32) 
BufferColor (V3 Float) (V3 Int16) = Normalized (B3 Int16) 
BufferColor (V3 Float) (V3 Int8) = Normalized (B3 Int8) 
BufferColor (V3 Float) (V3 Word32) = Normalized (B3 Word32) 
BufferColor (V3 Float) (V3 Word16) = Normalized (B3 Word16) 
BufferColor (V3 Float) (V3 Word8) = Normalized (B3 Word8) 
BufferColor (V3 Float) (V3 Float) = B3 Float 
BufferColor (V3 Int) (V3 Int32) = B3 Int32 
BufferColor (V3 Int) (V3 Int16) = B3 Int16 
BufferColor (V3 Int) (V3 Int8) = B3 Int8 
BufferColor (V3 Word) (V3 Word32) = B3 Word32 
BufferColor (V3 Word) (V3 Word16) = B3 Word16 
BufferColor (V3 Word) (V3 Word8) = B3 Word8 
BufferColor (V4 Float) (V4 Int32) = Normalized (B4 Int32) 
BufferColor (V4 Float) (V4 Int16) = Normalized (B4 Int16) 
BufferColor (V4 Float) (V4 Int8) = Normalized (B4 Int8) 
BufferColor (V4 Float) (V4 Word32) = Normalized (B4 Word32) 
BufferColor (V4 Float) (V4 Word16) = Normalized (B4 Word16) 
BufferColor (V4 Float) (V4 Word8) = Normalized (B4 Word8) 
BufferColor (V4 Float) (V4 Float) = B4 Float 
BufferColor (V4 Int) (V4 Int32) = B4 Int32 
BufferColor (V4 Int) (V4 Int16) = B4 Int16 
BufferColor (V4 Int) (V4 Int8) = B4 Int8 
BufferColor (V4 Word) (V4 Word32) = B4 Word32 
BufferColor (V4 Word) (V4 Word16) = B4 Word16 
BufferColor (V4 Word) (V4 Word8) = B4 Word8