Safe Haskell | None |
---|---|
Language | Haskell98 |
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
and B3
a
where B4
aa
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.
- data Buffer os b
- class BufferFormat f where
- type HostFormat f
- toBuffer :: ToBuffer (HostFormat f) f
- data ToBuffer a b
- data B a
- data B2 a
- data B3 a
- data B4 a
- data BPacked a
- newtype Normalized a = Normalized a
- newBuffer :: (MonadIO m, BufferFormat b) => Int -> ContextT w os f m (Buffer os b)
- bufferLength :: Buffer os b -> Int
- writeBuffer :: MonadIO m => Buffer os b -> BufferStartPos -> [HostFormat b] -> ContextT w os f m ()
- copyBuffer :: MonadIO m => Buffer os b -> BufferStartPos -> Buffer os b -> BufferStartPos -> Int -> ContextT w os f m ()
- type BufferStartPos = Int
- type family BufferColor c h
Buffer data type
A Buffer os b
lives in the object space os
and contains elements of type b
.
class BufferFormat f where Source
The class that constraints which types can live in a buffer.
type HostFormat f Source
The type a value of this format has when it lives on the host (i.e. normal Haskell world)
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 ...
Atomic buffer types
These types represent primitive host values such as Float
and Int32
in a buffer.
, B2
a
and B3
a
represent vectors of 2, 3 and 4 values of host type B4
aa
.
You cannot do anything special with values of these lifted types (like add two
s), only convert it into something useful later, e.g. in a B
Float
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
which will be automatically padded when necessary).
B3
a
The atomic buffer value that represents a host value of type a
.
BufferFormat (B Float) | |
BufferFormat (B Int32) | |
BufferFormat (B Word32) | |
VertexInput (Normalized (B Int32)) | |
VertexInput (Normalized (B Word32)) | |
VertexInput (B Float) | |
VertexInput (B Int32) | |
VertexInput (B Word32) | |
UniformInput (B Float) | |
UniformInput (B Int32) | |
UniformInput (B Word32) | |
type HostFormat (B Float) = Float | |
type HostFormat (B Int32) = Int32 | |
type HostFormat (B Word32) = Word32 | |
type VertexFormat (Normalized (B Int32)) = VFloat | |
type VertexFormat (Normalized (B Word32)) = VFloat | |
type VertexFormat (B Float) = VFloat | |
type VertexFormat (B Int32) = VInt | |
type VertexFormat (B Word32) = VWord | |
type UniformFormat (B Float) x = S x Float | |
type UniformFormat (B Int32) x = S x Int | |
type UniformFormat (B Word32) x = S x Word |
An atomic buffer value that represents a vector of 2 a
s on the host.
An atomic buffer value that represents a vector of 3 a
s on the host.
An atomic buffer value that represents a vector of 4 a
s on the host. This works similar to '(B a, B a, B a, B a)' but has some performance advantage, especially when used
in VertexArray
s.
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
.
BufferFormat (BPacked Word8) | |
BufferFormat (BPacked Word16) | |
type HostFormat (BPacked Word8) = Word8 | |
type HostFormat (BPacked Word16) = 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
).
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
.
type BufferStartPos = Int Source
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.