Safe Haskell | None |
---|---|
Language | Haskell98 |
Graphics.GPipe.FragmentStream
Description
A PrimitiveStream
can be rasterized, i.e. chopped up in pixel sized fragments, each of which contains an interpolated value of the primitives vertices, producing
a FragmentStream
.
- data FragmentStream a
- class FragmentInput a where
- type FragmentFormat a
- toFragment :: ToFragment a (FragmentFormat a)
- data ToFragment a b
- data FlatVFloat = Flat VFloat
- data NoPerspectiveVFloat = NoPerspective VFloat
- rasterize :: forall p a s os f. FragmentInput a => (s -> (Side, ViewPort, DepthRange)) -> PrimitiveStream p (VPos, a) -> Shader os f s (FragmentStream (FragmentFormat a))
- type VPos = V4 VFloat
- data Side
- = Front
- | Back
- | FrontAndBack
- data ViewPort = ViewPort {
- viewPortLowerLeft :: V2 Int
- viewPortSize :: V2 Int
- data DepthRange = DepthRange {}
- filterFragments :: (a -> FBool) -> FragmentStream a -> FragmentStream a
- withRasterizedInfo :: (a -> RasterizedInfo -> b) -> FragmentStream a -> FragmentStream b
- data RasterizedInfo = RasterizedInfo {}
The data type
data FragmentStream a Source
A
is a stream of fragments of type FragmentStream
a a
. You may append FragmentStream
s using the Monoid
instance, and you
can operate a stream's values using the Functor
instance (this will result in a shader running on the GPU).
Instances
class FragmentInput a where Source
This class constraints which vertex types can be turned into fragment values, and what type those values have.
Associated Types
type FragmentFormat a Source
The type the vertex value will be turned into once it becomes a fragment value.
Methods
toFragment :: ToFragment a (FragmentFormat a) Source
An arrow action that turns a value from it's vertex representation to it's fragment representation. Use toFragment
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
FragmentInput () | |
FragmentInput VBool | |
FragmentInput VWord | |
FragmentInput VInt | |
FragmentInput VFloat | |
FragmentInput NoPerspectiveVFloat | |
FragmentInput FlatVFloat | |
FragmentInput a => FragmentInput (V3 a) | |
FragmentInput a => FragmentInput (V2 a) | |
FragmentInput a => FragmentInput (V4 a) | |
FragmentInput a => FragmentInput (V1 a) | |
FragmentInput a => FragmentInput (V0 a) | |
FragmentInput a => FragmentInput (Quaternion a) | |
FragmentInput a => FragmentInput (Plucker a) | |
(FragmentInput a, FragmentInput b) => FragmentInput (a, b) | |
(FragmentInput (f a), FragmentInput a, (~) * (FragmentFormat (f a)) (f (FragmentFormat a))) => FragmentInput (Point f a) | |
(FragmentInput a, FragmentInput b, FragmentInput c) => FragmentInput (a, b, c) | |
(FragmentInput a, FragmentInput b, FragmentInput c, FragmentInput d) => FragmentInput (a, b, c, d) |
data FlatVFloat Source
A float value that is not interpolated (like integers), and all fragments will instead get the value of the primitive's last vertex
Instances
data NoPerspectiveVFloat Source
A float value that doesn't get divided by the interpolated position's w-component during interpolation.
Constructors
NoPerspective VFloat |
Instances
Creating FragmentStreams
rasterize :: forall p a s os f. FragmentInput a => (s -> (Side, ViewPort, DepthRange)) -> PrimitiveStream p (VPos, a) -> Shader os f s (FragmentStream (FragmentFormat a)) Source
Rasterize a stream of primitives into fragments, using a Side
, Viewport
and DepthRange
from the shader environment.
Primitives will be transformed from canonical view space, i.e. [(-1,-1,-1),(1,1,1)], to the 2D space defined by the ViewPort
parameter and the depth range
defined by the DepthRange
parameter.
Defines which side to rasterize. Non triangle primitives only has a front side.
Constructors
Front | |
Back | |
FrontAndBack |
The viewport in pixel coordinates (where (0,0) is the lower left corner) in to which the canonical view volume [(-1,-1,-1),(1,1,1)] is transformed and clipped/scissored.
Constructors
ViewPort | |
Fields
|
data DepthRange Source
The fragment depth range to map the canonical view volume's z-coordinate to. Depth values are clamped to [0,1], so DepthRange 0 1
gives maximum depth resolution.
Constructors
DepthRange | |
Various FragmentStream operations
filterFragments :: (a -> FBool) -> FragmentStream a -> FragmentStream a Source
Filter out fragments from the stream where the predicate in the first argument evaluates to true
, and discard all other fragments.
withRasterizedInfo :: (a -> RasterizedInfo -> b) -> FragmentStream a -> FragmentStream b Source
Like fmap
, but where various auto generated information from the rasterization is provided for each vertex.
data RasterizedInfo Source
Constructors
RasterizedInfo | |
Fields
|