fwgl-0.1.3.0: Game engine

Safe HaskellNone
LanguageHaskell2010

FWGL.Shader

Description

An example of shader variable:

        newtype Transform2 = Transform2 Mat3
                deriving (Typeable,
                          ShaderType, -- This is a type in the GPU (3x3 matrix).
                          UniformCPU CMat3) -- This can be used as an uniform
                                            -- and you can set it using a CPU
                                            -- 3x3 matrix
                                            -- (FWGL.Vector.Mat3)

An example of vertex shader:

        vertexShader :: VertexShader
        -- The types of the uniforms:
                                '[Transform2, View2, Depth]
        -- The types of the attributes:
                                '[Position2, UV]
        -- The types of the varying (outputs), excluding VertexShaderOutput.
                                '[UV]
        vertexShader 
        -- Set of uniforms:
                     (Transform2 trans :- View2 view :- Depth z :- N)
        -- Set of attributes:
                     (Position2 (Vec2 x y) :- uv@(UV _) :- N) =
        -- Matrix and vector multiplication:
                        let Vec3 x' y' _ = view * trans * Vec3 x y 1
        -- Set of outputs:
                        in Vertex (Vec4 x' y' z 1) -- Vertex position.
                           :- uv :- N

Required extensions:

{-# LANGUAGE DataKinds, RebindableSyntax, DeriveDataTypeable,
             GeneralizedNewtypeDeriving, GADTs #-}

Synopsis

Documentation

type Shader gs is os = STList gs -> STList is -> STList os Source

A function from a (heterogeneous) set of uniforms and a set of inputs (attributes or varyings) to a set of outputs (varyings).

type VertexShader g i o = Shader g i (VertexShaderOutput : o) Source

A Shader with a VertexShaderOutput output.

type FragmentShader g i = Shader g i (FragmentShaderOutput : `[]`) Source

A Shader with only a FragmentShaderOutput output.

newtype VertexShaderOutput Source

The position of the vertex.

Constructors

Vertex Vec4 

newtype FragmentShaderOutput Source

The RGBA color of the fragment (1.0 = #FF).

Constructors

Fragment Vec4 

class Typeable a

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

class AllTypeable xs Source

Instances

AllTypeable ([] *) Source 
(Typeable * x, AllTypeable xs) => AllTypeable ((:) * x xs) Source 

data Sampler2D Source

A GPU sampler (sampler2D in GLSL).

data Vec2 Source

A GPU 2D vector. NB: This is a different type from Data.Vect.Float.Vec2.

Constructors

Vec2 Float Float 

type CFloat = Float Source

Floats in the CPU.

type CSampler2D = ActiveTexture Source

Samplers in the CPU.

type CVec2 = Vec2 Source

2D vectors in the CPU.

type CVec3 = Vec3 Source

3D vectors in the CPU.

type CVec4 = Vec4 Source

4D vectors in the CPU.

type CMat2 = Mat2 Source

2x2 matrices in the CPU.

type CMat3 = Mat3 Source

3x3 matrices in the CPU.

type CMat4 = Mat4 Source

4x4 matrices in the CPU.

negate :: GenType a => a -> a Source

(*) :: (Mul a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c infixl 7 Source

(/) :: (Mul a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c infixl 7 Source

(+) :: (Sum a, ShaderType a) => a -> a -> a infixl 6 Source

(-) :: (Sum a, ShaderType a) => a -> a -> a infixl 6 Source

(^) :: (ShaderType a, ShaderType b) => a -> b -> a infixr 8 Source

(&&) :: Bool -> Bool -> Bool infixr 3 Source

(||) :: Bool -> Bool -> Bool infixr 2 Source

(==) :: ShaderType a => a -> a -> Bool infix 4 Source

(>=) :: ShaderType a => a -> a -> Bool infix 4 Source

(<=) :: ShaderType a => a -> a -> Bool infix 4 Source

(<) :: ShaderType a => a -> a -> Bool infix 4 Source

(>) :: ShaderType a => a -> a -> Bool infix 4 Source

ifThenElse :: ShaderType a => Bool -> a -> a -> a Source

Rebound if. You don't need to use this function, with -XRebindableSyntax.

loop Source

Arguments

:: ShaderType a 
=> Float

Maximum number of iterations (should be as low as possible, must be an integer literal)

-> a

Initial value

-> (Float -> a -> (a, Bool))

Iteration -> Old value -> (Next, Stop)

-> a 

true :: Bool Source

false :: Bool Source

store :: ShaderType a => a -> a Source

Avoid executing this expression more than one time. Conditionals and loops imply it.

radians :: GenType a => a -> a Source

degrees :: GenType a => a -> a Source

sin :: GenType a => a -> a Source

cos :: GenType a => a -> a Source

tan :: GenType a => a -> a Source

asin :: GenType a => a -> a Source

acos :: GenType a => a -> a Source

atan :: GenType a => a -> a Source

atan2 :: GenType a => a -> a -> a Source

exp :: GenType a => a -> a Source

log :: GenType a => a -> a Source

exp2 :: GenType a => a -> a Source

log2 :: GenType a => a -> a Source

sqrt :: GenType a => a -> a Source

inversesqrt :: GenType a => a -> a Source

abs :: GenType a => a -> a Source

sign :: GenType a => a -> a Source

floor :: GenType a => a -> a Source

ceil :: GenType a => a -> a Source

fract :: GenType a => a -> a Source

mod :: (GenType a, GenType b) => a -> b -> a Source

min :: GenType a => a -> a -> a Source

max :: GenType a => a -> a -> a Source

clamp :: (GenType a, GenType b) => a -> b -> b -> a Source

mix :: (GenType a, GenType b) => a -> a -> b -> a Source

step :: GenType a => a -> a -> a Source

smoothstep :: (GenType a, GenType b) => b -> b -> a -> a Source

length :: GenType a => a -> Float Source

distance :: GenType a => a -> a -> Float Source

dot :: GenType a => a -> a -> Float Source

normalize :: GenType a => a -> a Source

faceforward :: GenType a => a -> a -> a -> a Source

reflect :: GenType a => a -> a -> a Source

refract :: GenType a => a -> a -> Float -> a Source

matrixCompMult :: (Matrix a, Matrix b, Matrix c) => a -> b -> c Source

position :: Vec4 Source

The position of the vertex (only works in the vertex shader).

fragColor :: Vec4 Source

The color of the fragment (only works in the fragment shader).

data STList :: [*] -> * where Source

An heterogeneous set of ShaderTypes and Typeables.

Constructors

N :: STList `[]` 
(:-) :: (ShaderType a, Typeable a, IsMember a xs ~ False) => a -> STList xs -> STList (a : xs) infixr 4 

(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9

Function composition.

id :: a -> a

Identity function.

const :: a -> b -> a

Constant function.

flip :: (a -> b -> c) -> b -> a -> c

flip f takes its (first) two arguments in the reverse order of f.

($) :: (a -> b) -> a -> b infixr 0

Application operator. This operator is redundant, since ordinary application (f x) means the same as (f $ x). However, $ has low, right-associative binding precedence, so it sometimes allows parentheses to be omitted; for example:

    f $ g $ h x  =  f (g (h x))

It is also useful in higher-order situations, such as map ($ 0) xs, or zipWith ($) fs xs.

fst :: (a, b) -> a

Extract the first component of a pair.

snd :: (a, b) -> b

Extract the second component of a pair.