Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type VPos = V4 VFloat
- type ExprPos = ExprM ()
- type RasterizationName = Int
- data FragmentStreamData = FragmentStreamData RasterizationName Bool ExprPos PrimitiveStreamData FBool
- newtype FragmentStream a = FragmentStream [(a, FragmentStreamData)]
- newtype ToFragment a b = ToFragment (Kleisli (State Int) a b)
- class FragmentInput a where
- type FragmentFormat a
- toFragment :: ToFragment a (FragmentFormat a)
- rasterize :: forall p a s os f. FragmentInput a => (s -> (Side, PolygonMode, ViewPort, DepthRange)) -> PrimitiveStream p (VPos, a) -> Shader os s (FragmentStream (FragmentFormat a))
- data Side
- = Front
- | Back
- | FrontAndBack
- data PolygonMode
- data ViewPort = ViewPort {
- viewPortLowerLeft :: V2 Int
- viewPortSize :: V2 Int
- data DepthRange = DepthRange {}
- filterFragments :: (a -> FBool) -> FragmentStream a -> FragmentStream a
- data RasterizedInfo = RasterizedInfo {}
- withRasterizedInfo :: (a -> RasterizedInfo -> b) -> FragmentStream a -> FragmentStream b
- data FlatVFloat = Flat VFloat
- data NoPerspectiveVFloat = NoPerspective VFloat
- makeFragment :: String -> SType -> (a -> ExprM String) -> ToFragment a (S c a1)
- unFlat :: FlatVFloat -> VFloat
- unNPersp :: NoPerspectiveVFloat -> VFloat
Documentation
type RasterizationName = Int Source #
data FragmentStreamData Source #
newtype 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).
FragmentStream [(a, FragmentStreamData)] |
Instances
Functor FragmentStream Source # | |
Defined in Graphics.GPipe.Internal.FragmentStream fmap :: (a -> b) -> FragmentStream a -> FragmentStream b # (<$) :: a -> FragmentStream b -> FragmentStream a # | |
Semigroup (FragmentStream a) Source # | |
Defined in Graphics.GPipe.Internal.FragmentStream (<>) :: FragmentStream a -> FragmentStream a -> FragmentStream a # sconcat :: NonEmpty (FragmentStream a) -> FragmentStream a # stimes :: Integral b => b -> FragmentStream a -> FragmentStream a # | |
Monoid (FragmentStream a) Source # | |
Defined in Graphics.GPipe.Internal.FragmentStream mempty :: FragmentStream a # mappend :: FragmentStream a -> FragmentStream a -> FragmentStream a # mconcat :: [FragmentStream a] -> FragmentStream a # |
newtype ToFragment a b Source #
The arrow type for toFragment
.
ToFragment (Kleisli (State Int) a b) |
Instances
Arrow ToFragment Source # | |
Defined in Graphics.GPipe.Internal.FragmentStream arr :: (b -> c) -> ToFragment b c # first :: ToFragment b c -> ToFragment (b, d) (c, d) # second :: ToFragment b c -> ToFragment (d, b) (d, c) # (***) :: ToFragment b c -> ToFragment b' c' -> ToFragment (b, b') (c, c') # (&&&) :: ToFragment b c -> ToFragment b c' -> ToFragment b (c, c') # | |
Category ToFragment Source # | |
Defined in Graphics.GPipe.Internal.FragmentStream id :: forall (a :: k). ToFragment a a # (.) :: forall (b :: k) (c :: k) (a :: k). ToFragment b c -> ToFragment a b -> ToFragment a c # |
class FragmentInput a where Source #
This class constraints which vertex types can be turned into fragment values, and what type those values have.
type FragmentFormat a Source #
The type the vertex value will be turned into once it becomes a fragment value.
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
rasterize :: forall p a s os f. FragmentInput a => (s -> (Side, PolygonMode, ViewPort, DepthRange)) -> PrimitiveStream p (VPos, a) -> Shader os s (FragmentStream (FragmentFormat a)) Source #
Rasterize a stream of primitives into fragments, using a Side
,
PolygonMode
, 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. PolygonMode
controls whether to fill in the primitives or whether to show a wireframe
or points only.
Defines which side to rasterize. Non triangle primitives only has a front side.
data PolygonMode Source #
Defines whether to fill the polygon or to show points or wireframes.
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.
ViewPort | |
|
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.
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.
data RasterizedInfo Source #
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 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.
Instances
makeFragment :: String -> SType -> (a -> ExprM String) -> ToFragment a (S c a1) Source #
unFlat :: FlatVFloat -> VFloat Source #
unNPersp :: NoPerspectiveVFloat -> VFloat Source #