| Safe Haskell | None | 
|---|---|
| Language | Haskell98 | 
Graphics.GPipe.Expr
Contents
Description
This module provides the DSL for shader operations in GPipe. The type S x aa in a shader stage x, eg S F Float means a
 floating point value in a fragment stream.
- data S x a
- data V
- data F
- type VFloat = S V Float
- type VInt = S V Int
- type VWord = S V Word
- type VBool = S V Bool
- type FFloat = S F Float
- type FInt = S F Int
- type FWord = S F Word
- type FBool = S F Bool
- class Convert a where- type ConvertFloat a
- type ConvertInt a
- type ConvertWord a
- toFloat :: a -> ConvertFloat a
- toInt :: a -> ConvertInt a
- toWord :: a -> ConvertWord a
 
- class Integral' a where
- class (IfB a, OrdB a, Floating a) => Real' a where
- dFdx :: FFloat -> FFloat
- dFdy :: FFloat -> FFloat
- fwidth :: FFloat -> FFloat
- data ShaderBase a x
- class ShaderType a x where- type ShaderBaseType a
- toBase :: x -> a -> ShaderBase (ShaderBaseType a) x
- fromBase :: x -> ShaderBase (ShaderBaseType a) x -> a
 
- while :: forall a x. ShaderType a x => (a -> S x Bool) -> (a -> a) -> a -> a
- ifThen :: forall a x. ShaderType a x => S x Bool -> (a -> a) -> a -> a
- ifThenElse :: forall a b x. (ShaderType a x, ShaderType b x) => S x Bool -> (a -> b) -> (a -> b) -> a -> b
- ifThenElse' :: forall a x. ShaderType a x => S x Bool -> a -> a -> a
Atomic shader type
Instances
Instances
| FragmentInput VBool | |
| FragmentInput VWord | |
| FragmentInput VInt | |
| FragmentInput VFloat | |
| type FragmentFormat VBool = FBool | |
| type FragmentFormat VWord = FWord | |
| type FragmentFormat VInt = FInt | |
| type FragmentFormat VFloat = FFloat | 
Type classes where the Prelude ones are lacking
Provides a common way to convert numeric types to integer and floating point representations.
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 (IfB a, OrdB a, 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' or ceiling'.
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
data ShaderBase a x Source
class ShaderType a x where Source
Associated Types
type ShaderBaseType a Source
Methods
toBase :: x -> a -> ShaderBase (ShaderBaseType a) x Source
fromBase :: x -> ShaderBase (ShaderBaseType a) x -> a Source
Instances
| ShaderType () x | |
| ShaderType a x => ShaderType (V3 a) x | |
| ShaderType a x => ShaderType (V2 a) x | |
| ShaderType a x => ShaderType (V4 a) x | |
| ShaderType a x => ShaderType (V1 a) x | |
| ShaderType a x => ShaderType (V0 a) x | |
| (ShaderType a x, ShaderType b x) => ShaderType (a, b) x | |
| ShaderType (S x Bool) x | |
| ShaderType (S x Word) x | |
| ShaderType (S x Int) x | |
| ShaderType (S x Float) x | |
| (ShaderType a x, ShaderType b x, ShaderType c x) => ShaderType (a, b, c) x | |
| (ShaderType a x, ShaderType b x, ShaderType c x, ShaderType d x) => ShaderType (a, b, c, d) x | 
while :: forall a x. ShaderType a x => (a -> S x Bool) -> (a -> a) -> a -> a Source
ifThen :: forall a x. ShaderType a x => S x Bool -> (a -> a) -> a -> a Source
ifThenElse :: forall a b x. (ShaderType a x, ShaderType b x) => S x Bool -> (a -> b) -> (a -> b) -> a -> b Source
ifThenElse' :: forall a x. ShaderType a x => S x Bool -> a -> a -> a Source