ombra-1.1.0.0: Render engine.

LicenseBSD3
Maintainerziocroc@gmail.com
Stabilityexperimental
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Shader

Contents

Description

 

Synopsis

Documentation

data Shader s i o Source #

A function that runs in the GPU.

Instances

Arrow (Shader s) Source # 

Methods

arr :: (b -> c) -> Shader s b c #

first :: Shader s b c -> Shader s (b, d) (c, d) #

second :: Shader s b c -> Shader s (d, b) (d, c) #

(***) :: Shader s b c -> Shader s b' c' -> Shader s (b, b') (c, c') #

(&&&) :: Shader s b c -> Shader s b c' -> Shader s b (c, c') #

ArrowChoice (Shader s) Source # 

Methods

left :: Shader s b c -> Shader s (Either b d) (Either c d) #

right :: Shader s b c -> Shader s (Either d b) (Either d c) #

(+++) :: Shader s b c -> Shader s b' c' -> Shader s (Either b b') (Either c c') #

(|||) :: Shader s b d -> Shader s c d -> Shader s (Either b c) d #

ArrowApply (Shader s) Source # 

Methods

app :: Shader s (Shader s b c, b) c #

Category * (Shader s) Source # 

Methods

id :: cat a a #

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

(ShaderInput a, MultiShaderType b) => HasTrie (Shader s a b) Source # 

Associated Types

data (Shader s a b) :->: b :: * #

Methods

trie :: (Shader s a b -> b) -> Shader s a b :->: b #

untrie :: (Shader s a b :->: b) -> Shader s a b -> b #

enumerate :: (Shader s a b :->: b) -> [(Shader s a b, b)] #

(ShaderInput i, ShaderInput o) => Hashable (Shader s i o) Source # 

Methods

hashWithSalt :: Int -> Shader s i o -> Int #

hash :: Shader s i o -> Int #

(ShaderInput a, MultiShaderType b) => MultiShaderType (Shader s a b) Source # 

Associated Types

type ExprMST (Shader s a b) :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> Shader s a b -> Shader s a b Source #

toExprMST :: Shader s a b -> ExprMST (Shader s a b) Source #

fromExprMST :: ExprMST (Shader s a b) -> Shader s a b Source #

data (:->:) (Shader s a b) Source # 
data (:->:) (Shader s a b) = SFunTrie ((:->:) (ExprMST (Shader s a b)) c)
type ExprMST (Shader s a b) Source # 
type ExprMST (Shader s a b)

type VertexShader = Shader VertexShaderStage Source #

A shader that transforms vertices.

type FragmentShader = Shader FragmentShaderStage Source #

A shader that transforms fragments.

Uniforms

uniform :: forall u s. Uniform u => Shader s (CPUUniform u) u Source #

Add a shader variable that can be set with a CPU value.

(~<) :: Uniform u => Shader s (u, i) o -> CPUUniform u -> Shader s i o infixl 9 Source #

Add a uniform and directly set it with the second operand.

foldUniforms :: forall a u s. (ShaderInput a, ArrayUniform u, GLES) => Shader s ((a -> u -> a, a), [CPUBase u]) a Source #

Create an array uniform and then fold over it with the given function and initial value.

Optimized shaders

shader :: (MultiShaderType i, MultiShaderType o) => Shader s i o -> Shader s i o Source #

Create a shader function that can be reused efficiently. Ideally, every operation on G* and *Sampler types should be performed by a top level Shader created with this function, while arrow combinators and uniforms can appear anywhere.

sarr :: (MultiShaderType i, MultiShaderType o) => (i -> o) -> Shader s i o Source #

shaderParam :: (HasTrie p, MultiShaderType i, MultiShaderType o) => Shader s (p, i) o -> Shader s (p, i) o Source #

This variant of shader can be used with shaders that have a mostly static parameter. It will create a different shader every time the parameter changes to a new value, therefore parameters should not be used for things like model matrices (for which uniforms are more appropriate). Unlike uniforms, parameters can be used anywhere, in particular they can be used to change the shader structure. Shaders themselves can be used as parameters.

pshader :: (HasTrie p, MultiShaderType i, MultiShaderType o) => (p -> Shader s i o) -> p -> Shader s i o Source #

See shaderParam. The result of partially applying this function is a function for which the same rules of shader apply (that is, it should be reused rather than recreated at every frame).

ushader :: (MultiShaderType i, MultiShaderType o) => (UniformSetter x -> Shader s i o) -> UniformSetter x -> Shader s i o Source #

shader with an additional parameter that can be used to set the values of the uniforms. Like pshader, this should be used as a function of functions, not a function with two arguments.

pushader :: (HasTrie p, MultiShaderType i, MultiShaderType o) => (p -> UniformSetter x -> Shader s i o) -> p -> UniformSetter x -> Shader s i o Source #

Combination of pshader and ushader.

(~<*) :: Uniform u => Shader s (u, i) o -> UniformSetter (CPUUniform u) -> Shader s i o infixl 9 Source #

Add a uniform and directly set it with a UniformSetter.

Fragment shader functionalities

data Fragment Source #

Constructors

Fragment 

Fields

  • fragCoord :: GVec4

    The coordinates of the fragment.

  • fragFrontFacing :: GBool

    If the fragment belongs to a front-facing primitive.

  • dFdx :: forall a. GenType a => a -> a

    Partial derivative of the argument with respect to the window X coordinate.

  • dFdy :: forall a. GenType a => a -> a

    Partial derivative of the argument with respect to the window Y coordinate.

  • fwidth :: forall a. GenType a => a -> a

    Sum of the absolute values of dFdx and dFdy.

farr :: (MultiShaderType i, MultiShaderType o) => (Fragment -> i -> o) -> FragmentShader i o Source #

This works like sarr but provides a Fragment.

Loops

forLoop Source #

Arguments

:: ShaderInput a 
=> Int

Maximum number of iterations (should be as low as possible)

-> a

Initial value

-> (GInt -> a -> (a, GBool))

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

-> a 

Repeatedly apply a function to a shader value. This is compiled to an actual for loop, therefore it won't duplicate the function code (doing that could slow down compilation or cause an out of memory error). The same applies to derived functions like foldGArray and foldUniforms.

foldGArray :: forall t n a. (ShaderType t, KnownNat n, ShaderInput a) => (a -> t -> a) -> a -> GArray n t -> a Source #

Classes

class HasTrie (ExprMST a) => MultiShaderType a where Source #

Types that contain zero or more ShaderTypes.

Associated Types

type ExprMST a Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> a -> a Source #

mapMST :: (Generic a, GMultiShaderType (Rep a)) => (forall x. ShaderType x => x -> x) -> a -> a Source #

toExprMST :: a -> ExprMST a Source #

toExprMST :: (Generic a, GMultiShaderType (Rep a), ExprMST a ~ GExprMST (Rep a)) => a -> ExprMST a Source #

fromExprMST :: ExprMST a -> a Source #

fromExprMST :: (Generic a, GMultiShaderType (Rep a), ExprMST a ~ GExprMST (Rep a)) => ExprMST a -> a Source #

Instances

MultiShaderType () Source # 

Associated Types

type ExprMST () :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> () -> () Source #

toExprMST :: () -> ExprMST () Source #

fromExprMST :: ExprMST () -> () Source #

MultiShaderType GMat4 Source # 

Associated Types

type ExprMST GMat4 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GMat4 -> GMat4 Source #

toExprMST :: GMat4 -> ExprMST GMat4 Source #

fromExprMST :: ExprMST GMat4 -> GMat4 Source #

MultiShaderType GMat3 Source # 

Associated Types

type ExprMST GMat3 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GMat3 -> GMat3 Source #

toExprMST :: GMat3 -> ExprMST GMat3 Source #

fromExprMST :: ExprMST GMat3 -> GMat3 Source #

MultiShaderType GMat2 Source # 

Associated Types

type ExprMST GMat2 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GMat2 -> GMat2 Source #

toExprMST :: GMat2 -> ExprMST GMat2 Source #

fromExprMST :: ExprMST GMat2 -> GMat2 Source #

MultiShaderType GBVec4 Source # 

Associated Types

type ExprMST GBVec4 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GBVec4 -> GBVec4 Source #

toExprMST :: GBVec4 -> ExprMST GBVec4 Source #

fromExprMST :: ExprMST GBVec4 -> GBVec4 Source #

MultiShaderType GBVec3 Source # 

Associated Types

type ExprMST GBVec3 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GBVec3 -> GBVec3 Source #

toExprMST :: GBVec3 -> ExprMST GBVec3 Source #

fromExprMST :: ExprMST GBVec3 -> GBVec3 Source #

MultiShaderType GBVec2 Source # 

Associated Types

type ExprMST GBVec2 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GBVec2 -> GBVec2 Source #

toExprMST :: GBVec2 -> ExprMST GBVec2 Source #

fromExprMST :: ExprMST GBVec2 -> GBVec2 Source #

MultiShaderType GIVec4 Source # 

Associated Types

type ExprMST GIVec4 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GIVec4 -> GIVec4 Source #

toExprMST :: GIVec4 -> ExprMST GIVec4 Source #

fromExprMST :: ExprMST GIVec4 -> GIVec4 Source #

MultiShaderType GIVec3 Source # 

Associated Types

type ExprMST GIVec3 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GIVec3 -> GIVec3 Source #

toExprMST :: GIVec3 -> ExprMST GIVec3 Source #

fromExprMST :: ExprMST GIVec3 -> GIVec3 Source #

MultiShaderType GIVec2 Source # 

Associated Types

type ExprMST GIVec2 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GIVec2 -> GIVec2 Source #

toExprMST :: GIVec2 -> ExprMST GIVec2 Source #

fromExprMST :: ExprMST GIVec2 -> GIVec2 Source #

MultiShaderType GVec4 Source # 

Associated Types

type ExprMST GVec4 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GVec4 -> GVec4 Source #

toExprMST :: GVec4 -> ExprMST GVec4 Source #

fromExprMST :: ExprMST GVec4 -> GVec4 Source #

MultiShaderType GVec3 Source # 

Associated Types

type ExprMST GVec3 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GVec3 -> GVec3 Source #

toExprMST :: GVec3 -> ExprMST GVec3 Source #

fromExprMST :: ExprMST GVec3 -> GVec3 Source #

MultiShaderType GVec2 Source # 

Associated Types

type ExprMST GVec2 :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GVec2 -> GVec2 Source #

toExprMST :: GVec2 -> ExprMST GVec2 Source #

fromExprMST :: ExprMST GVec2 -> GVec2 Source #

MultiShaderType GInt Source # 

Associated Types

type ExprMST GInt :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GInt -> GInt Source #

toExprMST :: GInt -> ExprMST GInt Source #

fromExprMST :: ExprMST GInt -> GInt Source #

MultiShaderType GFloat Source # 

Associated Types

type ExprMST GFloat :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GFloat -> GFloat Source #

toExprMST :: GFloat -> ExprMST GFloat Source #

fromExprMST :: ExprMST GFloat -> GFloat Source #

MultiShaderType GBool Source # 

Associated Types

type ExprMST GBool :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GBool -> GBool Source #

toExprMST :: GBool -> ExprMST GBool Source #

fromExprMST :: ExprMST GBool -> GBool Source #

MultiShaderType DepthBufferSampler Source # 
MultiShaderType a => MultiShaderType [a] Source # 

Associated Types

type ExprMST [a] :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> [a] -> [a] Source #

toExprMST :: [a] -> ExprMST [a] Source #

fromExprMST :: ExprMST [a] -> [a] Source #

FragmentShaderOutput o => MultiShaderType (GBufferSampler o) Source # 

Associated Types

type ExprMST (GBufferSampler o) :: * Source #

(ShaderInput a, MultiShaderType b) => MultiShaderType (a -> b) Source # 

Associated Types

type ExprMST (a -> b) :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> (a -> b) -> a -> b Source #

toExprMST :: (a -> b) -> ExprMST (a -> b) Source #

fromExprMST :: ExprMST (a -> b) -> a -> b Source #

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

Associated Types

type ExprMST (a, b) :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> (a, b) -> (a, b) Source #

toExprMST :: (a, b) -> ExprMST (a, b) Source #

fromExprMST :: ExprMST (a, b) -> (a, b) Source #

(KnownNat n, ShaderType t) => MultiShaderType (GArray n t) Source # 

Associated Types

type ExprMST (GArray n t) :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> GArray n t -> GArray n t Source #

toExprMST :: GArray n t -> ExprMST (GArray n t) Source #

fromExprMST :: ExprMST (GArray n t) -> GArray n t Source #

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

Associated Types

type ExprMST (a, b, c) :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> (a, b, c) -> (a, b, c) Source #

toExprMST :: (a, b, c) -> ExprMST (a, b, c) Source #

fromExprMST :: ExprMST (a, b, c) -> (a, b, c) Source #

(ShaderInput a, MultiShaderType b) => MultiShaderType (Shader s a b) Source # 

Associated Types

type ExprMST (Shader s a b) :: * Source #

Methods

mapMST :: (forall x. ShaderType x => x -> x) -> Shader s a b -> Shader s a b Source #

toExprMST :: Shader s a b -> ExprMST (Shader s a b) Source #

fromExprMST :: ExprMST (Shader s a b) -> Shader s a b Source #

class MultiShaderType a => ShaderInput a where Source #

Types that contain a finite amount of ShaderTypes.

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (a, Int) Source #

buildMST :: (Generic a, GShaderInput (Rep a)) => (forall x. ShaderType x => Int -> x) -> Int -> (a, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> a -> b Source #

foldrMST :: (Generic a, GShaderInput (Rep a)) => (forall x. ShaderType x => x -> b -> b) -> b -> a -> b Source #

Instances

ShaderInput () Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> ((), Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> () -> b Source #

ShaderInput GMat4 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GMat4, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GMat4 -> b Source #

ShaderInput GMat3 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GMat3, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GMat3 -> b Source #

ShaderInput GMat2 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GMat2, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GMat2 -> b Source #

ShaderInput GBVec4 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GBVec4, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GBVec4 -> b Source #

ShaderInput GBVec3 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GBVec3, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GBVec3 -> b Source #

ShaderInput GBVec2 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GBVec2, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GBVec2 -> b Source #

ShaderInput GIVec4 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GIVec4, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GIVec4 -> b Source #

ShaderInput GIVec3 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GIVec3, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GIVec3 -> b Source #

ShaderInput GIVec2 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GIVec2, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GIVec2 -> b Source #

ShaderInput GVec4 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GVec4, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GVec4 -> b Source #

ShaderInput GVec3 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GVec3, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GVec3 -> b Source #

ShaderInput GVec2 Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GVec2, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GVec2 -> b Source #

ShaderInput GInt Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GInt, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GInt -> b Source #

ShaderInput GFloat Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GFloat, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GFloat -> b Source #

ShaderInput GBool Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GBool, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GBool -> b Source #

ShaderInput DepthBufferSampler Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (DepthBufferSampler, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> DepthBufferSampler -> b Source #

FragmentShaderOutput o => ShaderInput (GBufferSampler o) Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GBufferSampler o, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GBufferSampler o -> b Source #

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

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> ((a, b), Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> (a, b) -> b Source #

(KnownNat n, ShaderType t) => ShaderInput (GArray n t) Source # 

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> (GArray n t, Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> GArray n t -> b Source #

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

Methods

buildMST :: (forall x. ShaderType x => Int -> x) -> Int -> ((a, b, c), Int) Source #

foldrMST :: (forall x. ShaderType x => x -> b -> b) -> b -> (a, b, c) -> b Source #

class (ShaderInput o, KnownNat (NFloats o)) => FragmentShaderOutput o where Source #

Types that contain GFloats.

Associated Types

type NFloats o :: Nat Source #

Methods

fromGFloats :: [GFloat] -> (o, [GFloat]) Source #

fromGFloats :: (Generic o, GFragmentShaderOutput (Rep o)) => [GFloat] -> (o, [GFloat]) Source #

toGFloats :: o -> [GFloat] -> [GFloat] Source #

toGFloats :: (Generic o, GFragmentShaderOutput (Rep o)) => o -> [GFloat] -> [GFloat] Source #

Instances

FragmentShaderOutput () Source # 

Associated Types

type NFloats () :: Nat Source #

Methods

fromGFloats :: [GFloat] -> ((), [GFloat]) Source #

toGFloats :: () -> [GFloat] -> [GFloat] Source #

FragmentShaderOutput GVec4 Source # 

Associated Types

type NFloats GVec4 :: Nat Source #

FragmentShaderOutput GVec3 Source # 

Associated Types

type NFloats GVec3 :: Nat Source #

FragmentShaderOutput GVec2 Source # 

Associated Types

type NFloats GVec2 :: Nat Source #

FragmentShaderOutput GFloat Source # 

Associated Types

type NFloats GFloat :: Nat Source #

(FragmentShaderOutput a, FragmentShaderOutput b, KnownNat ((+) (NFloats a) (NFloats b))) => FragmentShaderOutput (a, b) Source # 

Associated Types

type NFloats (a, b) :: Nat Source #

Methods

fromGFloats :: [GFloat] -> ((a, b), [GFloat]) Source #

toGFloats :: (a, b) -> [GFloat] -> [GFloat] Source #

(FragmentShaderOutput a, FragmentShaderOutput b, FragmentShaderOutput c, KnownNat ((+) ((+) (NFloats a) (NFloats b)) (NFloats c))) => FragmentShaderOutput (a, b, c) Source # 

Associated Types

type NFloats (a, b, c) :: Nat Source #

Methods

fromGFloats :: [GFloat] -> ((a, b, c), [GFloat]) Source #

toGFloats :: (a, b, c) -> [GFloat] -> [GFloat] Source #

class MapShader f s | f -> s where Source #

Minimal complete definition

mapShader

Methods

mapShader :: Shader s i o -> f i -> f o Source #

class ShaderInput a => Uniform a where Source #

Types that contain uniform values.

Associated Types

type CPUUniform a Source #

Methods

foldrUniform :: Proxy a -> (UniformValue -> b -> b) -> b -> CPUUniform a -> b Source #

foldrUniform :: (Generic a, Generic (CPUUniform a), GUniform (Rep a) (Rep (CPUUniform a))) => Proxy a -> (UniformValue -> b -> b) -> b -> CPUUniform a -> b Source #

Instances

Uniform () Source # 

Associated Types

type CPUUniform () :: * Source #

Methods

foldrUniform :: Proxy * () -> (UniformValue -> b -> b) -> b -> CPUUniform () -> b Source #

GLES => Uniform GMat4 Source # 

Associated Types

type CPUUniform GMat4 :: * Source #

Methods

foldrUniform :: Proxy * GMat4 -> (UniformValue -> b -> b) -> b -> CPUUniform GMat4 -> b Source #

GLES => Uniform GMat3 Source # 

Associated Types

type CPUUniform GMat3 :: * Source #

Methods

foldrUniform :: Proxy * GMat3 -> (UniformValue -> b -> b) -> b -> CPUUniform GMat3 -> b Source #

GLES => Uniform GMat2 Source # 

Associated Types

type CPUUniform GMat2 :: * Source #

Methods

foldrUniform :: Proxy * GMat2 -> (UniformValue -> b -> b) -> b -> CPUUniform GMat2 -> b Source #

GLES => Uniform GBVec4 Source # 

Associated Types

type CPUUniform GBVec4 :: * Source #

Methods

foldrUniform :: Proxy * GBVec4 -> (UniformValue -> b -> b) -> b -> CPUUniform GBVec4 -> b Source #

GLES => Uniform GBVec3 Source # 

Associated Types

type CPUUniform GBVec3 :: * Source #

Methods

foldrUniform :: Proxy * GBVec3 -> (UniformValue -> b -> b) -> b -> CPUUniform GBVec3 -> b Source #

GLES => Uniform GBVec2 Source # 

Associated Types

type CPUUniform GBVec2 :: * Source #

Methods

foldrUniform :: Proxy * GBVec2 -> (UniformValue -> b -> b) -> b -> CPUUniform GBVec2 -> b Source #

GLES => Uniform GIVec4 Source # 

Associated Types

type CPUUniform GIVec4 :: * Source #

Methods

foldrUniform :: Proxy * GIVec4 -> (UniformValue -> b -> b) -> b -> CPUUniform GIVec4 -> b Source #

GLES => Uniform GIVec3 Source # 

Associated Types

type CPUUniform GIVec3 :: * Source #

Methods

foldrUniform :: Proxy * GIVec3 -> (UniformValue -> b -> b) -> b -> CPUUniform GIVec3 -> b Source #

GLES => Uniform GIVec2 Source # 

Associated Types

type CPUUniform GIVec2 :: * Source #

Methods

foldrUniform :: Proxy * GIVec2 -> (UniformValue -> b -> b) -> b -> CPUUniform GIVec2 -> b Source #

GLES => Uniform GVec4 Source # 

Associated Types

type CPUUniform GVec4 :: * Source #

Methods

foldrUniform :: Proxy * GVec4 -> (UniformValue -> b -> b) -> b -> CPUUniform GVec4 -> b Source #

GLES => Uniform GVec3 Source # 

Associated Types

type CPUUniform GVec3 :: * Source #

Methods

foldrUniform :: Proxy * GVec3 -> (UniformValue -> b -> b) -> b -> CPUUniform GVec3 -> b Source #

GLES => Uniform GVec2 Source # 

Associated Types

type CPUUniform GVec2 :: * Source #

Methods

foldrUniform :: Proxy * GVec2 -> (UniformValue -> b -> b) -> b -> CPUUniform GVec2 -> b Source #

GLES => Uniform GInt Source # 

Associated Types

type CPUUniform GInt :: * Source #

Methods

foldrUniform :: Proxy * GInt -> (UniformValue -> b -> b) -> b -> CPUUniform GInt -> b Source #

GLES => Uniform GFloat Source # 

Associated Types

type CPUUniform GFloat :: * Source #

Methods

foldrUniform :: Proxy * GFloat -> (UniformValue -> b -> b) -> b -> CPUUniform GFloat -> b Source #

GLES => Uniform GBool Source # 

Associated Types

type CPUUniform GBool :: * Source #

Methods

foldrUniform :: Proxy * GBool -> (UniformValue -> b -> b) -> b -> CPUUniform GBool -> b Source #

Uniform DepthBufferSampler Source # 

Associated Types

type CPUUniform DepthBufferSampler :: * Source #

Methods

foldrUniform :: Proxy * DepthBufferSampler -> (UniformValue -> b -> b) -> b -> CPUUniform DepthBufferSampler -> b Source #

FragmentShaderOutput o => Uniform (GBufferSampler o) Source # 

Associated Types

type CPUUniform (GBufferSampler o) :: * Source #

Methods

foldrUniform :: Proxy * (GBufferSampler o) -> (UniformValue -> b -> b) -> b -> CPUUniform (GBufferSampler o) -> b Source #

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

Associated Types

type CPUUniform (a, b) :: * Source #

Methods

foldrUniform :: Proxy * (a, b) -> (UniformValue -> b -> b) -> b -> CPUUniform (a, b) -> b Source #

(KnownNat n, ShaderType t, BaseUniform (GArray n t), GLES) => Uniform (GArray n t) Source # 

Associated Types

type CPUUniform (GArray n t) :: * Source #

Methods

foldrUniform :: Proxy * (GArray n t) -> (UniformValue -> b -> b) -> b -> CPUUniform (GArray n t) -> b Source #

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

Associated Types

type CPUUniform (a, b, c) :: * Source #

Methods

foldrUniform :: Proxy * (a, b, c) -> (UniformValue -> b -> b) -> b -> CPUUniform (a, b, c) -> b Source #