Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- data PrimitiveStream t a
- class VertexInput a where
- type VertexFormat a
- toVertex :: ToVertex a (VertexFormat a)
- data ToVertex a b
- toPrimitiveStream :: forall os f s a p. (PrimitiveTopology p, VertexInput a) => (s -> PrimitiveArray p a) -> Shader os s (PrimitiveStream p (VertexFormat a))
- toPrimitiveStream' :: forall os f s a b p. (PrimitiveTopology p, VertexInput a) => Maybe (s -> Buffer os b) -> (s -> PrimitiveArray p a) -> Shader os s (PrimitiveStream p (VertexFormat a))
- withInputIndices :: (a -> InputIndices -> b) -> PrimitiveStream p a -> PrimitiveStream p b
- data InputIndices = InputIndices {}
- withPointSize :: (a -> PointSize -> (b, PointSize)) -> PrimitiveStream Points a -> PrimitiveStream Points b
- type PointSize = VFloat
The data type
data PrimitiveStream t a Source #
A
is a stream of primitives of
type PrimitiveStream
t a 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 PrimitiveStream
s using the Monoid
instance, but if possible append the origin PrimitiveArray
s instead, as this will create more optimized
draw calls.
Instances
Functor (PrimitiveStream t) Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveStream fmap :: (a -> b) -> PrimitiveStream t a -> PrimitiveStream t b # (<$) :: a -> PrimitiveStream t b -> PrimitiveStream t a # | |
Semigroup (PrimitiveStream t a) Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveStream (<>) :: PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a # sconcat :: NonEmpty (PrimitiveStream t a) -> PrimitiveStream t a # stimes :: Integral b => b -> PrimitiveStream t a -> PrimitiveStream t a # | |
Monoid (PrimitiveStream t a) Source # | |
Defined in Graphics.GPipe.Internal.PrimitiveStream mempty :: PrimitiveStream t a # mappend :: PrimitiveStream t a -> PrimitiveStream t a -> PrimitiveStream t a # mconcat :: [PrimitiveStream t a] -> PrimitiveStream t a # |
class VertexInput a where Source #
This class constraints which buffer types can be turned into vertex values, and what type those values have.
type VertexFormat a Source #
The type the buffer value will be turned into once it becomes a vertex value.
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
The arrow type for toVertex
.
Creating PrimitiveStreams
toPrimitiveStream :: forall os f s a p. (PrimitiveTopology p, VertexInput a) => (s -> PrimitiveArray p a) -> Shader os s (PrimitiveStream p (VertexFormat a)) Source #
Create a primitive stream from a primitive array provided from the shader environment.
TODO No way to constraint b
a bit more?
toPrimitiveStream' :: forall os f s a b p. (PrimitiveTopology p, VertexInput a) => Maybe (s -> Buffer os b) -> (s -> PrimitiveArray p a) -> Shader os s (PrimitiveStream p (VertexFormat a)) Source #
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.
data InputIndices Source #
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.