GPipe-2.2.5: Typesafe functional GPU graphics programming

Safe HaskellNone
LanguageHaskell98

Graphics.GPipe.FragmentStream

Contents

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.

Synopsis

The data type

data FragmentStream a Source #

A FragmentStream a is a stream of fragments of type a. You may append FragmentStreams 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).

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 () Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat () :: Type Source #

FragmentInput VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VBool :: Type Source #

FragmentInput VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VWord :: Type Source #

FragmentInput VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VInt :: Type Source #

FragmentInput VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VFloat :: Type Source #

FragmentInput NoPerspectiveVFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

FragmentInput FlatVFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat FlatVFloat :: Type Source #

FragmentInput a => FragmentInput (Plucker a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (Plucker a) :: Type Source #

FragmentInput a => FragmentInput (Quaternion a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (Quaternion a) :: Type Source #

FragmentInput a => FragmentInput (V0 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V0 a) :: Type Source #

FragmentInput a => FragmentInput (V4 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V4 a) :: Type Source #

FragmentInput a => FragmentInput (V3 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V3 a) :: Type Source #

FragmentInput a => FragmentInput (V2 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V2 a) :: Type Source #

FragmentInput a => FragmentInput (V1 a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V1 a) :: Type Source #

(FragmentInput a, FragmentInput b) => FragmentInput (a, b) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (a, b) :: Type Source #

Methods

toFragment :: ToFragment (a, b) (FragmentFormat (a, b)) Source #

(FragmentInput (f a), FragmentInput a, FragmentFormat (f a) ~ f (FragmentFormat a)) => FragmentInput (Point f a) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (Point f a) :: Type Source #

(FragmentInput a, FragmentInput b, FragmentInput c) => FragmentInput (a, b, c) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (a, b, c) :: Type Source #

Methods

toFragment :: ToFragment (a, b, c) (FragmentFormat (a, b, c)) Source #

(FragmentInput a, FragmentInput b, FragmentInput c, FragmentInput d) => FragmentInput (a, b, c, d) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (a, b, c, d) :: Type Source #

Methods

toFragment :: ToFragment (a, b, c, d) (FragmentFormat (a, b, c, d)) Source #

(FragmentInput a, FragmentInput b, FragmentInput c, FragmentInput d, FragmentInput e) => FragmentInput (a, b, c, d, e) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (a, b, c, d, e) :: Type Source #

Methods

toFragment :: ToFragment (a, b, c, d, e) (FragmentFormat (a, b, c, d, e)) Source #

(FragmentInput a, FragmentInput b, FragmentInput c, FragmentInput d, FragmentInput e, FragmentInput f) => FragmentInput (a, b, c, d, e, f) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (a, b, c, d, e, f) :: Type Source #

Methods

toFragment :: ToFragment (a, b, c, d, e, f) (FragmentFormat (a, b, c, d, e, f)) Source #

(FragmentInput a, FragmentInput b, FragmentInput c, FragmentInput d, FragmentInput e, FragmentInput f, FragmentInput g) => FragmentInput (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (a, b, c, d, e, f, g) :: Type Source #

Methods

toFragment :: ToFragment (a, b, c, d, e, f, g) (FragmentFormat (a, b, c, d, e, f, g)) Source #

data ToFragment a b Source #

The arrow type for toFragment.

Instances
Arrow ToFragment Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Methods

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 # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Methods

id :: ToFragment a a #

(.) :: ToFragment b c -> ToFragment a b -> ToFragment a c #

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

Constructors

Flat VFloat 

data NoPerspectiveVFloat Source #

A float value that doesn't get divided by the interpolated position's w-component during interpolation.

Constructors

NoPerspective VFloat 

Creating FragmentStreams

rasterize :: forall p a s os f. FragmentInput a => (s -> (Side, ViewPort, DepthRange)) -> PrimitiveStream p (VPos, a) -> Shader os 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.

data Side Source #

Defines which side to rasterize. Non triangle primitives only has a front side.

Constructors

Front 
Back 
FrontAndBack 

data ViewPort Source #

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 

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 

Fields

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.