luminance-0.11: Type-safe, type-level and stateless graphics framework

Copyright(C) 2015, 2016 Dimitri Sabadie
LicenseBSD3
MaintainerDimitri Sabadie <dimitri.sabadie@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Graphics.Luminance.Shader.Program

Contents

Description

 

Synopsis

Shader program creation

data Program u Source

Shader program.

Instances

Eq u => Eq (Program u) Source 
Show u => Show (Program u) Source 

createProgram :: (HasProgramError e, MonadError e m, MonadIO m, MonadResource m) => [Stage] -> ((forall a. UniformName a -> UniformInterface m (U a)) -> UniformInterface m i) -> m (Program i) Source

Create a new shader Program.

That function takes a list of Stages and a uniform interface builder function and yields a Program and the interface.

The builder function takes a function you can use to retrieve uniforms. You can pass values of type UniformName to identify the uniform you want to retrieve. If the uniform can’t be retrieved, throws InactiveUniform.

In the end, you get the new Program and a polymorphic value you can choose the type of in the function you pass as argument. You can use that value to gather uniforms for instance.

createProgram_ :: (HasProgramError e, MonadError e m, MonadIO m, MonadResource m) => [Stage] -> m (Program ()) Source

A simpler version of createProgram. That function assumes you don’t need a uniform interface and then just returns the Program.

Uniform

class Uniform a Source

Class of types that can be sent down to shaders. That class is closed because shaders cannot handle a lot of uniform types. However, you should have a look at the U documentation for further information about how to augment the scope of the types you can send down to shaders.

Minimal complete definition

toU

Instances

Uniform Float Source 
Uniform Int32 Source 
Uniform Word32 Source 
Uniform () Source 
Uniform [Float] Source 
Uniform [Int32] Source 
Uniform [Word32] Source 
Uniform [(Float, Float)] Source 
Uniform [(Int32, Int32)] Source 
Uniform [(Word32, Word32)] Source 
Uniform [(Float, Float, Float)] Source 
Uniform [(Int32, Int32, Int32)] Source 
Uniform [(Word32, Word32, Word32)] Source 
Uniform [(Float, Float, Float, Float)] Source 
Uniform [(Int32, Int32, Int32, Int32)] Source 
Uniform [(Word32, Word32, Word32, Word32)] Source 
Uniform [M44 Float] Source 
Uniform [V Nat 2 Float] Source 
Uniform [V Nat 2 Int32] Source 
Uniform [V Nat 2 Word32] Source 
Uniform [V Nat 3 Float] Source 
Uniform [V Nat 3 Int32] Source 
Uniform [V Nat 3 Word32] Source 
Uniform [V Nat 4 Float] Source 
Uniform [V Nat 4 Int32] Source 
Uniform [V Nat 4 Word32] Source 
Uniform [V4 Float] Source 
Uniform [V4 Int32] Source 
Uniform [V4 Word32] Source 
Uniform [V3 Float] Source 
Uniform [V3 Int32] Source 
Uniform [V3 Word32] Source 
Uniform [V2 Float] Source 
Uniform [V2 Int32] Source 
Uniform [V2 Word32] Source 
Uniform (M44 Float) Source 
Uniform (V4 Float) Source 
Uniform (V4 Int32) Source 
Uniform (V4 Word32) Source 
Uniform (V3 Float) Source 
Uniform (V3 Int32) Source 
Uniform (V3 Word32) Source 
Uniform (V2 Float) Source 
Uniform (V2 Int32) Source 
Uniform (V2 Word32) Source 
Pixel f => Uniform (Cubemap f) Source 
Pixel f => Uniform (Texture1D f) Source 
Pixel f => Uniform (Texture2D f) Source 
Pixel f => Uniform (Texture3D f) Source 
Uniform (Float, Float) Source 
Uniform (Int32, Int32) Source 
Uniform (Word32, Word32) Source 
Uniform (Float, Float, Float) Source 
Uniform (Int32, Int32, Int32) Source 
Uniform (Word32, Word32, Word32) Source 
Uniform (V Nat 2 Float) Source 
Uniform (V Nat 2 Int32) Source 
Uniform (V Nat 2 Word32) Source 
Uniform (V Nat 3 Float) Source 
Uniform (V Nat 3 Int32) Source 
Uniform (V Nat 3 Word32) Source 
Uniform (V Nat 4 Float) Source 
Uniform (V Nat 4 Int32) Source 
Uniform (V Nat 4 Word32) Source 
Uniform (Float, Float, Float, Float) Source 
Uniform (Int32, Int32, Int32, Int32) Source 
Uniform (Word32, Word32, Word32, Word32) Source 

data U a Source

A shader uniform. U a doesn’t hold any value. It’s more like a mapping between the host code and the shader the uniform was retrieved from.

U is contravariant in its argument. That means that you can use contramap to build more interesting uniform types.

Another interesting part is the fact that U is also monoidal. You can accumulate several of them with '(<>)' if they have the same type. That means that you can join them so that when you pass an actual value, it gets shared inside the resulting value.

The '()' instance doesn’t do anything and doesn’t even use its argument.

(.=) :: U a -> a -> U' Source

Feed U a with a value.

updateUniforms :: MonadIO m => Program a -> (a -> U') -> m () Source

Update uniforms in a program. That function enables you to update only the uniforms you want and not the whole.

If you want to update several uniforms (not only one), you can use the 'Semigroup'/'Monoid' instances (use '(<>)' or 'sconcat'/'mconcat' for instance).

data UniformName :: * -> * where Source

Possible way to name uniform values.

data SomeUniformName Source

A uniform name with type-erasure. You can only access the constructors and the carried name but you can’t reconstruct the phantom type.

Constructors

forall a . SomeUniformName (UniformName a) 

Uniform block

newtype UB a Source

Constructors

UB 

Fields

unUB :: a
 

Error handling

data ProgramError Source

Shader program error.

'LinkFailed reason' happens when a program fails to link. reason contains the error message.

'InactiveUniform uni' happens at linking when a uniform is inactive in the program; that is, unused or semantically set to a negative value.

class HasProgramError a where Source

Types that can handle ProgramError – read as, “have”.

Re-exported

(<>) :: Semigroup a => a -> a -> a

An associative operation.

(a <> b) <> c = a <> (b <> c)

If a is also a Monoid we further require

(<>) = mappend

sconcat :: Semigroup a => NonEmpty a -> a

Reduce a non-empty list with <>

The default definition should be sufficient, but this can be overridden for efficiency.