Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class BufferFormat f where
- type HostFormat f
- toBuffer :: ToBuffer (HostFormat f) f
- getGlType :: f -> GLenum
- peekPixel :: f -> Ptr () -> IO (HostFormat f)
- getGlPaddedFormat :: f -> GLenum
- type family BufferColor c h where ...
- data Buffer os b
- data ToBuffer a b = ToBuffer !(Kleisli (StateT Offset (WriterT [Int] (Reader (UniformAlignment, AlignmentMode)))) a b) !(Kleisli (StateT Offset (Reader (BufferName, Stride, BInput))) a b) !(Kleisli (StateT (Ptr (), [Int]) IO) a b) !AlignmentMode
- data B a = B {}
- newtype B2 a = B2 {}
- newtype B3 a = B3 {}
- newtype B4 a = B4 {}
- toB22 :: forall a. (Storable a, BufferFormat (B2 a)) => B4 a -> (B2 a, B2 a)
- toB3 :: forall a. (Storable a, BufferFormat (B3 a)) => B4 a -> B3 a
- toB21 :: forall a. (Storable a, BufferFormat (B a)) => B3 a -> (B2 a, B a)
- toB12 :: forall a. (Storable a, BufferFormat (B a)) => B3 a -> (B a, B2 a)
- toB11 :: forall a. (Storable a, BufferFormat (B a)) => B2 a -> (B a, B a)
- newtype Uniform a = Uniform a
- newtype Normalized a = Normalized a
- data BPacked a
- data BInput = BInput {
- bInSkipElems :: Int
- bInInstanceDiv :: Int
- newBuffer :: (MonadIO m, BufferFormat b, ContextHandler ctx) => Int -> ContextT ctx os m (Buffer os b)
- writeBuffer :: (ContextHandler ctx, MonadIO m) => Buffer os b -> BufferStartPos -> [HostFormat b] -> ContextT ctx os m ()
- copyBuffer :: (ContextHandler ctx, MonadIO m) => Buffer os b -> BufferStartPos -> Buffer os b -> BufferStartPos -> Int -> ContextT ctx os m ()
- type BufferStartPos = Int
- bufSize :: forall os b. Buffer os b -> Int
- bufName :: Buffer os b -> BufferName
- bufElementSize :: Buffer os b -> Int
- bufferLength :: Buffer os b -> Int
- bufBElement :: Buffer os b -> BInput -> b
- bufTransformFeedback :: Buffer os b -> IORef (Maybe (GLuint, GLuint))
- bufferWriteInternal :: Buffer os f -> Ptr () -> [HostFormat f] -> IO (Ptr ())
- makeBuffer :: forall os b. BufferFormat b => BufferName -> Int -> UniformAlignment -> Buffer os b
- getUniformAlignment :: IO Int
- type UniformAlignment = Int
Documentation
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 ...
getGlType :: f -> GLenum Source #
peekPixel :: f -> Ptr () -> IO (HostFormat f) Source #
getGlPaddedFormat :: f -> GLenum Source #
Instances
type family BufferColor c h where ... 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.
A Buffer os b
lives in the object space os
and contains elements of type b
.
The arrow type for toBuffer
.
ToBuffer !(Kleisli (StateT Offset (WriterT [Int] (Reader (UniformAlignment, AlignmentMode)))) a b) !(Kleisli (StateT Offset (Reader (BufferName, Stride, BInput))) a b) !(Kleisli (StateT (Ptr (), [Int]) IO) a b) !AlignmentMode |
The atomic buffer value that represents a host value of type a
.
Instances
An atomic buffer value that represents a vector of 2 a
s on the host.
Instances
An atomic buffer value that represents a vector of 3 a
s on the host.
Instances
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.
Instances
toB11 :: forall a. (Storable a, BufferFormat (B a)) => B2 a -> (B a, B a) Source #
Split up a
into two B2
a
s.B1
a
Any buffer value that is going to be used as a uniform needs to be wrapped in this newtype. This will cause is to be aligned properly for uniform usage. It can still be used as input for vertex arrays, but due to the uniform alignment it will probably be padded quite heavily and thus wasteful.
Uniform a |
Instances
BufferFormat a => BufferFormat (Uniform a) Source # | |
Defined in Graphics.GPipe.Internal.Buffer type HostFormat (Uniform a) Source # | |
type HostFormat (Uniform a) Source # | |
Defined in Graphics.GPipe.Internal.Buffer |
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
).
Instances
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
.
Instances
BufferFormat (BPacked Word8) Source # | |
Defined in Graphics.GPipe.Internal.Buffer type HostFormat (BPacked Word8) Source # | |
BufferFormat (BPacked Word16) Source # | |
Defined in Graphics.GPipe.Internal.Buffer type HostFormat (BPacked Word16) Source # | |
type HostFormat (BPacked Word8) Source # | |
Defined in Graphics.GPipe.Internal.Buffer | |
type HostFormat (BPacked Word16) Source # | |
Defined in Graphics.GPipe.Internal.Buffer |
BInput | |
|
newBuffer :: (MonadIO m, BufferFormat b, ContextHandler ctx) => Int -> ContextT ctx os m (Buffer os b) Source #
Create a buffer with a specified number of elements.
writeBuffer :: (ContextHandler ctx, MonadIO m) => Buffer os b -> BufferStartPos -> [HostFormat b] -> ContextT ctx os m () Source #
Write a buffer from the host (i.e. the normal Haskell world).
copyBuffer :: (ContextHandler ctx, MonadIO m) => Buffer os b -> BufferStartPos -> Buffer os b -> BufferStartPos -> Int -> ContextT ctx os 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 #
bufElementSize :: Buffer os b -> Int Source #
bufferLength :: Buffer os b -> Int Source #
Retrieve the number of elements in a buffer.
bufBElement :: Buffer os b -> BInput -> b Source #
bufferWriteInternal :: Buffer os f -> Ptr () -> [HostFormat f] -> IO (Ptr ()) Source #
makeBuffer :: forall os b. BufferFormat b => BufferName -> Int -> UniformAlignment -> Buffer os b Source #
type UniformAlignment = Int Source #