GPipe-2.0.2: 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 
FragmentInput VWord 
FragmentInput VInt 
FragmentInput VFloat 
Floating (S a Float) 
Fractional (S a Float) 
Num (S a Word) 
Num (S a Int) 
Num (S a Float) 
Ord x => OrdB (S a x) 
IfB (S a x) 
Eq x => EqB (S a x) 
Boolean (S a Bool) 
Conjugate (S a Word) 
Conjugate (S a Int) 
Conjugate (S a Float) 
TrivialConjugate (S a Word) 
TrivialConjugate (S a Int) 
TrivialConjugate (S a Float) 
Convert (S x Word) 
Convert (S x Int) 
Convert (S x Float) 
Real' (S x Float) 
Integral' (S a Word) 
Integral' (S a Int) 
ShaderType (S x Bool) x 
ShaderType (S x Word) x 
ShaderType (S x Int) x 
ShaderType (S x Float) x 
type FragmentFormat VBool = FBool 
type FragmentFormat VWord = FWord 
type FragmentFormat VInt = FInt 
type FragmentFormat VFloat = FFloat 
type BooleanOf (S a x) = S a Bool 
type ConvertFloat (S x Word) = S x Float 
type ConvertFloat (S x Int) = S x Float 
type ConvertFloat (S x Float) = S x Float 
type ConvertInt (S x Word) = S x Int 
type ConvertInt (S x Int) = S x Int 
type ConvertInt (S x Float) = S x Int 
type ConvertWord (S x Word) = S x Word 
type ConvertWord (S x Int) = S x Word 
type ConvertWord (S x Float) = S x Word 
type ShaderBaseType (S x Bool) = S x Bool 
type ShaderBaseType (S x Word) = S x Word 
type ShaderBaseType (S x Int) = S x Int 
type ShaderBaseType (S x Float) = S x Float 

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 Integral' a where Source

Methods

div' :: a -> a -> a Source

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

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'.

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

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

saturate :: a -> a Source

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

step :: a -> a -> a Source

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

Instances

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

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