GPipe-2.1.3: Typesafe functional GPU graphics programming

Safe HaskellNone
LanguageHaskell98

Graphics.GPipe.Expr

Contents

Description

This module provides the DSL for shader operations in GPipe. The type S x a is an opaque type that represents a value of type a in a shader stage x, eg S F Float means a floating point value in a fragment stream.

Synopsis

Atomic shader type

data S x a Source

Instances

FragmentInput VBool Source 
FragmentInput VWord Source 
FragmentInput VInt Source 
FragmentInput VFloat Source 
Floating (S a Float) Source 
Fractional (S a Float) Source 
Num (S a Word) Source 
Num (S a Int) Source 
Num (S a Float) Source 
Boolean (S a Bool) Source 
IfB (S a Bool) Source 
IfB (S a Word) Source 
IfB (S a Int) Source 
IfB (S a Float) Source 
Eq x => EqB (S a x) Source 
Ord x => OrdB (S a x) Source 
Conjugate (S a Word) Source 
Conjugate (S a Int) Source 
Conjugate (S a Float) Source 
TrivialConjugate (S a Word) Source 
TrivialConjugate (S a Int) Source 
TrivialConjugate (S a Float) Source 
Convert (S x Word) Source 
Convert (S x Int) Source 
Convert (S x Float) Source 
FloatingOrd (S x Float) Source 
Real' (S x Float) Source 
Integral' (S a Word) Source 
Integral' (S a Int) Source 
ShaderType (S x Bool) x Source 
ShaderType (S x Word) x Source 
ShaderType (S x Int) x Source 
ShaderType (S x Float) x Source 
type FragmentFormat VBool = FBool Source 
type FragmentFormat VWord = FWord Source 
type FragmentFormat VInt = FInt Source 
type FragmentFormat VFloat = FFloat Source 
type BooleanOf (S a x) = S a Bool Source 
type ConvertFloat (S x Word) = S x Float Source 
type ConvertFloat (S x Int) = S x Float Source 
type ConvertFloat (S x Float) = S x Float Source 
type ConvertInt (S x Word) = S x Int Source 
type ConvertInt (S x Int) = S x Int Source 
type ConvertInt (S x Float) = S x Int Source 
type ConvertWord (S x Word) = S x Word Source 
type ConvertWord (S x Int) = S x Word Source 
type ConvertWord (S x Float) = S x Word Source 
type ShaderBaseType (S x Bool) = S x Bool Source 
type ShaderBaseType (S x Word) = S x Word Source 
type ShaderBaseType (S x Int) = S x Int Source 
type ShaderBaseType (S x Float) = S x Float Source 

data V Source

Phantom type used as first argument in S V a that denotes that the shader value is a vertex value

data F Source

Phantom type used as first argument in S F a that denotes that the shader value is a fragment value

type VInt = S V Int Source

type FInt = S F Int Source

Type classes where the Prelude ones are lacking

class Convert a where Source

Provides a common way to convert numeric types to integer and floating point representations.

Associated Types

type ConvertFloat a Source

type ConvertInt a Source

type ConvertWord a Source

Methods

toFloat :: a -> ConvertFloat a Source

Convert to a floating point number.

toInt :: a -> ConvertInt a Source

Convert to an integral number, using truncation if necessary.

toWord :: a -> ConvertWord a Source

Convert to an unsigned integral number, using truncation if necessary.

class Floating a => Real' a where Source

This class provides the GPU functions either not found in Prelude's numerical classes, or that has wrong types. Instances are also provided for normal Floats and Doubles.

Minimal complete definition

floor' | ceiling'

Methods

rsqrt :: a -> a Source

exp2 :: a -> a Source

log2 :: a -> a Source

floor' :: a -> a Source

ceiling' :: a -> a Source

fract' :: a -> a Source

mod'' :: a -> a -> a Source

mix :: a -> a -> a -> a Source

Instances

class (IfB a, OrdB a, Floating a) => FloatingOrd a where Source

This class provides various order comparing functions

Minimal complete definition

Nothing

Methods

clamp :: a -> a -> a -> a Source

saturate :: a -> a Source

step :: a -> a -> a Source

smoothstep :: a -> a -> a -> a Source

Additional functions

dFdx :: FFloat -> FFloat Source

The derivative in x using local differencing of the rasterized value.

dFdy :: FFloat -> FFloat Source

The derivative in y using local differencing of the rasterized value.

fwidth :: FFloat -> FFloat Source

The sum of the absolute derivative in x and y using local differencing of the rasterized value.

Shader control structures

while :: forall a x. ShaderType a x => (a -> S x Bool) -> (a -> a) -> a -> a Source

while f g x will iteratively transform x with g as long as f generates true.

ifThen :: forall a x. ShaderType a x => S x Bool -> (a -> a) -> a -> a Source

ifThen c f x will return f x if c evaluates to true or x otherwise.

In most cases functionally equivalent to ifThenElse' but usually generate smaller shader code since the last argument is not inlined into the two branches, which also would affect implicit derivates (e.g. dFdx, dFdy or sampling using SampleAuto)

ifThenElse :: forall a b x. (ShaderType a x, ShaderType b x) => S x Bool -> (a -> b) -> (a -> b) -> a -> b Source

ifThenElse c f g x will return f x if c evaluates to true or g x otherwise.

In most cases functionally equivalent to ifThenElse' but usually generate smaller shader code since the last argument is not inlined into the two branches, which also would affect implicit derivates (e.g. dFdx, dFdy or sampling using SampleAuto)

ifThenElse' :: forall a x. ShaderType a x => S x Bool -> a -> a -> a Source

Works just like ifB, return second argument if first is true otherwise return third argument.

The difference from ifB is that it in most cases generate more efficient code when a is a compound type (e.g. a tuple or a vector). For simple types such as S x Float, ifThenElse' == ifB.

data ShaderBase a x Source

An opaque type

class ShaderType a x where Source

Constraint for types that may pass in and out of shader control structures. Define your own instances in terms of others and make sure to make toBase as lazy as possible.

Associated Types

type ShaderBaseType a Source

A base type that this type can convert into. Use the ShaderBaseType function on an existing instance of ShaderType to define this in your instance.

Methods

toBase :: x -> a -> ShaderBase (ShaderBaseType a) x Source

Convert this type to the shader base type. Make sure this is as lazy as possible (e.g. use tilde (~) on each pattern match).

fromBase :: x -> ShaderBase (ShaderBaseType a) x -> a Source

Convert back from the shader base type to this type.

Instances

ShaderType () x Source 
ShaderType a x => ShaderType (V4 a) x Source 
ShaderType a x => ShaderType (V3 a) x Source 
ShaderType a x => ShaderType (V2 a) x Source 
ShaderType a x => ShaderType (V1 a) x Source 
ShaderType a x => ShaderType (V0 a) x Source 
(ShaderType a x, ShaderType b x) => ShaderType (a, b) x Source 
ShaderType (S x Bool) x Source 
ShaderType (S x Word) x Source 
ShaderType (S x Int) x Source 
ShaderType (S x Float) x Source 
(ShaderType a x, ShaderType b x, ShaderType c x) => ShaderType (a, b, c) x Source 
(ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x) => ShaderType (a, b, c, d) x Source