GPipe-Core-0.2.3.1: Typesafe functional GPU graphics programming
Safe HaskellNone
LanguageHaskell2010

Graphics.GPipe.Internal.FragmentStream

Synopsis

Documentation

type ExprPos = ExprM () Source #

newtype 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).

Constructors

FragmentStream [(a, FragmentStreamData)] 

newtype ToFragment a b Source #

The arrow type for toFragment.

Constructors

ToFragment (Kleisli (State Int) a b) 

Instances

Instances details
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 :: 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.

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

Instances details
FragmentInput () Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat () Source #

FragmentInput VBool Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VBool Source #

FragmentInput VWord Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VWord Source #

FragmentInput VInt Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VInt Source #

FragmentInput VFloat Source # 
Instance details

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat VFloat 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 Source #

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

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (Plucker a) Source #

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

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (Quaternion a) Source #

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

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V0 a) Source #

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

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V4 a) Source #

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

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V3 a) Source #

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

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V2 a) Source #

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

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (V1 a) Source #

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

Defined in Graphics.GPipe.Internal.FragmentStream

Associated Types

type FragmentFormat (a, b) 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) 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) 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) 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) 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) 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) Source #

Methods

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

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.

data Side Source #

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

Constructors

Front 
Back 
FrontAndBack 

data PolygonMode Source #

Defines whether to fill the polygon or to show points or wireframes.

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

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.

newtype NoPerspectiveVFloat Source #

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

Constructors

NoPerspective VFloat 

makeFragment :: Text -> SType -> (a -> ExprM Text) -> ToFragment a (S c a1) Source #