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

Copyright(C) 2015 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

Shader program.

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)

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

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

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 
Uniform Int32 
Uniform Word32 
Uniform () 
Uniform [Float] 
Uniform [Int32] 
Uniform [Word32] 
Uniform [(Float, Float)] 
Uniform [(Int32, Int32)] 
Uniform [(Word32, Word32)] 
Uniform [(Float, Float, Float)] 
Uniform [(Int32, Int32, Int32)] 
Uniform [(Word32, Word32, Word32)] 
Uniform [(Float, Float, Float, Float)] 
Uniform [(Int32, Int32, Int32, Int32)] 
Uniform [(Word32, Word32, Word32, Word32)] 
Uniform [M44 Float] 
Uniform [V Nat 2 Float] 
Uniform [V Nat 2 Int32] 
Uniform [V Nat 2 Word32] 
Uniform [V Nat 3 Float] 
Uniform [V Nat 3 Int32] 
Uniform [V Nat 3 Word32] 
Uniform [V Nat 4 Float] 
Uniform [V Nat 4 Int32] 
Uniform [V Nat 4 Word32] 
Uniform [V4 Float] 
Uniform [V4 Int32] 
Uniform [V4 Word32] 
Uniform [V3 Float] 
Uniform [V3 Int32] 
Uniform [V3 Word32] 
Uniform [V2 Float] 
Uniform [V2 Int32] 
Uniform [V2 Word32] 
Uniform (M44 Float) 
Uniform (V4 Float) 
Uniform (V4 Int32) 
Uniform (V4 Word32) 
Uniform (V3 Float) 
Uniform (V3 Int32) 
Uniform (V3 Word32) 
Uniform (V2 Float) 
Uniform (V2 Int32) 
Uniform (V2 Word32) 
Pixel f => Uniform (Cubemap f) 
Pixel f => Uniform (Texture1D f) 
Pixel f => Uniform (Texture2D f) 
Pixel f => Uniform (Texture3D f) 
Uniform (Float, Float) 
Uniform (Int32, Int32) 
Uniform (Word32, Word32) 
Uniform (Float, Float, Float) 
Uniform (Int32, Int32, Int32) 
Uniform (Word32, Word32, Word32) 
Uniform (V Nat 2 Float) 
Uniform (V Nat 2 Int32) 
Uniform (V Nat 2 Word32) 
Uniform (V Nat 3 Float) 
Uniform (V Nat 3 Int32) 
Uniform (V Nat 3 Word32) 
Uniform (V Nat 4 Float) 
Uniform (V Nat 4 Int32) 
Uniform (V Nat 4 Word32) 
Uniform (Float, Float, Float, Float) 
Uniform (Int32, Int32, Int32, Int32) 
Uniform (Word32, Word32, Word32, Word32) 

data U a

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. It’s also a divisible contravariant functor, then you can divide structures to take advantage of divisible contravariant properties and then glue several U with different types. That can be useful to build a uniform type by gluing its fields.

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

data UniformName :: * -> * where

Possible way to name uniform values.

Uniform block

newtype UB a

Constructors

UB 

Fields

unUB :: a
 

Instances

Functor UB 
Foldable UB 
Traversable UB 
Eq a => Eq (UB a) 
Ord a => Ord (UB a) 
Show a => Show (UB a) 
UniformBlock a => Storable (UB a) 

Error handling

data ProgramError

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.

Constructors

LinkFailed String 
InactiveUniform SomeUniformName 

class HasProgramError a where

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