GPipe-2.2: Typesafe functional GPU graphics programming

Safe HaskellNone
LanguageHaskell98

Graphics.GPipe.Uniform

Description

Uniform values are constants that you can combine with all vertices or fragments of a PrimitiveStream or FragmentStream. They are loaded from a Buffer and OpenGl uniform blocks are used under the hood.

Synopsis

Documentation

class BufferFormat a => UniformInput a where Source #

This class constraints which buffer types can be loaded as uniforms, and what type those values have.

Minimal complete definition

toUniform

Associated Types

type UniformFormat a x Source #

The type the buffer value will be turned into once it becomes a vertex or fragment value (the x parameter is either V or F).

Methods

toUniform :: ToUniform x a (UniformFormat a x) Source #

An arrow action that turns a value from it's buffer representation to it's vertex or fragment representation. Use toUniform from the GPipe provided instances to operate in this arrow. Also note that this arrow needs to be able to return a value lazily, so ensure you use

proc ~pattern -> do ....

Instances

UniformInput () Source # 

Associated Types

type UniformFormat () x :: * Source #

Methods

toUniform :: ToUniform x () (UniformFormat () x) Source #

UniformInput a => UniformInput (Quaternion a) Source # 

Associated Types

type UniformFormat (Quaternion a) x :: * Source #

UniformInput a => UniformInput (Plucker a) Source # 

Associated Types

type UniformFormat (Plucker a) x :: * Source #

UniformInput a => UniformInput (V4 a) Source # 

Associated Types

type UniformFormat (V4 a) x :: * Source #

Methods

toUniform :: ToUniform x (V4 a) (UniformFormat (V4 a) x) Source #

UniformInput a => UniformInput (V3 a) Source # 

Associated Types

type UniformFormat (V3 a) x :: * Source #

Methods

toUniform :: ToUniform x (V3 a) (UniformFormat (V3 a) x) Source #

UniformInput a => UniformInput (V2 a) Source # 

Associated Types

type UniformFormat (V2 a) x :: * Source #

Methods

toUniform :: ToUniform x (V2 a) (UniformFormat (V2 a) x) Source #

UniformInput a => UniformInput (V1 a) Source # 

Associated Types

type UniformFormat (V1 a) x :: * Source #

Methods

toUniform :: ToUniform x (V1 a) (UniformFormat (V1 a) x) Source #

UniformInput a => UniformInput (V0 a) Source # 

Associated Types

type UniformFormat (V0 a) x :: * Source #

Methods

toUniform :: ToUniform x (V0 a) (UniformFormat (V0 a) x) Source #

UniformInput (B4 Float) Source # 

Associated Types

type UniformFormat (B4 Float) x :: * Source #

UniformInput (B4 Int32) Source # 

Associated Types

type UniformFormat (B4 Int32) x :: * Source #

UniformInput (B4 Word32) Source # 

Associated Types

type UniformFormat (B4 Word32) x :: * Source #

UniformInput (B3 Float) Source # 

Associated Types

type UniformFormat (B3 Float) x :: * Source #

UniformInput (B3 Int32) Source # 

Associated Types

type UniformFormat (B3 Int32) x :: * Source #

UniformInput (B3 Word32) Source # 

Associated Types

type UniformFormat (B3 Word32) x :: * Source #

UniformInput (B2 Float) Source # 

Associated Types

type UniformFormat (B2 Float) x :: * Source #

UniformInput (B2 Int32) Source # 

Associated Types

type UniformFormat (B2 Int32) x :: * Source #

UniformInput (B2 Word32) Source # 

Associated Types

type UniformFormat (B2 Word32) x :: * Source #

UniformInput (B Float) Source # 

Associated Types

type UniformFormat (B Float) x :: * Source #

UniformInput (B Int32) Source # 

Associated Types

type UniformFormat (B Int32) x :: * Source #

UniformInput (B Word32) Source # 

Associated Types

type UniformFormat (B Word32) x :: * Source #

(UniformInput a, UniformInput b) => UniformInput (a, b) Source # 

Associated Types

type UniformFormat (a, b) x :: * Source #

Methods

toUniform :: ToUniform x (a, b) (UniformFormat (a, b) x) Source #

(UniformInput a, UniformInput b, UniformInput c) => UniformInput (a, b, c) Source # 

Associated Types

type UniformFormat (a, b, c) x :: * Source #

Methods

toUniform :: ToUniform x (a, b, c) (UniformFormat (a, b, c) x) Source #

(UniformInput a, UniformInput b, UniformInput c, UniformInput d) => UniformInput (a, b, c, d) Source # 

Associated Types

type UniformFormat (a, b, c, d) x :: * Source #

Methods

toUniform :: ToUniform x (a, b, c, d) (UniformFormat (a, b, c, d) x) Source #

(UniformInput a, UniformInput b, UniformInput c, UniformInput d, UniformInput e) => UniformInput (a, b, c, d, e) Source # 

Associated Types

type UniformFormat (a, b, c, d, e) x :: * Source #

Methods

toUniform :: ToUniform x (a, b, c, d, e) (UniformFormat (a, b, c, d, e) x) Source #

(UniformInput a, UniformInput b, UniformInput c, UniformInput d, UniformInput e, UniformInput f) => UniformInput (a, b, c, d, e, f) Source # 

Associated Types

type UniformFormat (a, b, c, d, e, f) x :: * Source #

Methods

toUniform :: ToUniform x (a, b, c, d, e, f) (UniformFormat (a, b, c, d, e, f) x) Source #

(UniformInput a, UniformInput b, UniformInput c, UniformInput d, UniformInput e, UniformInput f, UniformInput g) => UniformInput (a, b, c, d, e, f, g) Source # 

Associated Types

type UniformFormat (a, b, c, d, e, f, g) x :: * Source #

Methods

toUniform :: ToUniform x (a, b, c, d, e, f, g) (UniformFormat (a, b, c, d, e, f, g) x) Source #

data ToUniform x a b Source #

The arrow type for toUniform.

Instances

Arrow (ToUniform x) Source # 

Methods

arr :: (b -> c) -> ToUniform x b c #

first :: ToUniform x b c -> ToUniform x (b, d) (c, d) #

second :: ToUniform x b c -> ToUniform x (d, b) (d, c) #

(***) :: ToUniform x b c -> ToUniform x b' c' -> ToUniform x (b, b') (c, c') #

(&&&) :: ToUniform x b c -> ToUniform x b c' -> ToUniform x b (c, c') #

Category * (ToUniform x) Source # 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

getUniform :: forall os f s b x. UniformInput b => (s -> (Buffer os (Uniform b), Int)) -> Shader os s (UniformFormat b x) Source #

Load a uniform value from a Buffer into a Shader. The argument function is used to retrieve the buffer and the index into this buffer from the shader environment.

newtype Uniform a Source #

Any buffer value that is going to be used as a uniform needs to be wrapped in this newtype. This will cause is to be aligned properly for uniform usage. It can still be used as input for vertex arrays, but due to the uniform alignment it will probably be padded quite heavily and thus wasteful.

Constructors

Uniform a