ombra-0.1.1.0: Render engine.

Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Shader.CPU

Synopsis

Documentation

data CPUSetterType k Source #

This kind represents the way you are setting a GPU value.

Constructors

S

Single CPU type (only for types with one field)

M

Mirror type (a data type identical to the GPU one but with CPU single types instead of GPU)

type family CPU (s :: CPUSetterType *) g where ... Source #

Equations

CPU S x = CPUSingle x 
CPU M x = CPUMirror x 

type family CPUBase g Source #

Instances

type CPUBase Mat4 Source # 
type CPUBase Mat3 Source # 
type CPUBase Mat2 Source # 
type CPUBase BVec4 Source # 
type CPUBase BVec3 Source # 
type CPUBase BVec2 Source # 
type CPUBase IVec4 Source # 
type CPUBase IVec3 Source # 
type CPUBase IVec2 Source # 
type CPUBase Vec4 Source # 
type CPUBase Vec3 Source # 
type CPUBase Vec2 Source # 
type CPUBase SamplerCube Source # 
type CPUBase Sampler2D Source # 
type CPUBase Int Source # 
type CPUBase Float Source # 
type CPUBase Bool Source # 
type CPUBase (Array n BVec4) Source # 
type CPUBase (Array n BVec4) = [IVec4]
type CPUBase (Array n BVec3) Source # 
type CPUBase (Array n BVec3) = [IVec3]
type CPUBase (Array n BVec2) Source # 
type CPUBase (Array n BVec2) = [IVec2]
type CPUBase (Array n IVec4) Source # 
type CPUBase (Array n IVec4) = [IVec4]
type CPUBase (Array n IVec3) Source # 
type CPUBase (Array n IVec3) = [IVec3]
type CPUBase (Array n IVec2) Source # 
type CPUBase (Array n IVec2) = [IVec2]
type CPUBase (Array n Vec4) Source # 
type CPUBase (Array n Vec4) = [Vec4]
type CPUBase (Array n Vec3) Source # 
type CPUBase (Array n Vec3) = [Vec3]
type CPUBase (Array n Vec2) Source # 
type CPUBase (Array n Vec2) = [Vec2]
type CPUBase (Array n Int) Source # 
type CPUBase (Array n Int) = [Int32]
type CPUBase (Array n Bool) Source # 
type CPUBase (Array n Bool) = [Int32]
type CPUBase (Array n Float) Source # 
type CPUBase (Array n Float) = [Float]

type family CPUMirror g Source #

The mirror type of a certain global.

For instance:

     data T = T Vec3 Float -- In the shader module
     data T = T Vec3 Float -- CPU version of the uniform type
     type CPUMirror GPU.T = T

class BaseUniform g where Source #

CPU types convertible to GPU types (as uniforms).

Minimal complete definition

setUniform

Methods

setUniform :: UniformLocation -> proxy g -> CPUBase g -> GL () Source #

Instances

GLES => BaseUniform Mat4 Source # 

Methods

setUniform :: UniformLocation -> proxy Mat4 -> CPUBase Mat4 -> GL () Source #

GLES => BaseUniform Mat3 Source # 

Methods

setUniform :: UniformLocation -> proxy Mat3 -> CPUBase Mat3 -> GL () Source #

GLES => BaseUniform Mat2 Source # 

Methods

setUniform :: UniformLocation -> proxy Mat2 -> CPUBase Mat2 -> GL () Source #

GLES => BaseUniform BVec4 Source # 

Methods

setUniform :: UniformLocation -> proxy BVec4 -> CPUBase BVec4 -> GL () Source #

GLES => BaseUniform BVec3 Source # 

Methods

setUniform :: UniformLocation -> proxy BVec3 -> CPUBase BVec3 -> GL () Source #

GLES => BaseUniform BVec2 Source # 

Methods

setUniform :: UniformLocation -> proxy BVec2 -> CPUBase BVec2 -> GL () Source #

GLES => BaseUniform IVec4 Source # 

Methods

setUniform :: UniformLocation -> proxy IVec4 -> CPUBase IVec4 -> GL () Source #

GLES => BaseUniform IVec3 Source # 

Methods

setUniform :: UniformLocation -> proxy IVec3 -> CPUBase IVec3 -> GL () Source #

GLES => BaseUniform IVec2 Source # 

Methods

setUniform :: UniformLocation -> proxy IVec2 -> CPUBase IVec2 -> GL () Source #

GLES => BaseUniform Vec4 Source # 

Methods

setUniform :: UniformLocation -> proxy Vec4 -> CPUBase Vec4 -> GL () Source #

GLES => BaseUniform Vec3 Source # 

Methods

setUniform :: UniformLocation -> proxy Vec3 -> CPUBase Vec3 -> GL () Source #

GLES => BaseUniform Vec2 Source # 

Methods

setUniform :: UniformLocation -> proxy Vec2 -> CPUBase Vec2 -> GL () Source #

GLES => BaseUniform SamplerCube Source # 
GLES => BaseUniform Sampler2D Source # 
GLES => BaseUniform Int Source # 

Methods

setUniform :: UniformLocation -> proxy Int -> CPUBase Int -> GL () Source #

GLES => BaseUniform Float Source # 

Methods

setUniform :: UniformLocation -> proxy Float -> CPUBase Float -> GL () Source #

GLES => BaseUniform Bool Source # 

Methods

setUniform :: UniformLocation -> proxy Bool -> CPUBase Bool -> GL () Source #

GLES => BaseUniform (Array n BVec4) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n BVec4) -> CPUBase (Array n BVec4) -> GL () Source #

GLES => BaseUniform (Array n BVec3) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n BVec3) -> CPUBase (Array n BVec3) -> GL () Source #

GLES => BaseUniform (Array n BVec2) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n BVec2) -> CPUBase (Array n BVec2) -> GL () Source #

GLES => BaseUniform (Array n IVec4) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n IVec4) -> CPUBase (Array n IVec4) -> GL () Source #

GLES => BaseUniform (Array n IVec3) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n IVec3) -> CPUBase (Array n IVec3) -> GL () Source #

GLES => BaseUniform (Array n IVec2) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n IVec2) -> CPUBase (Array n IVec2) -> GL () Source #

GLES => BaseUniform (Array n Vec4) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n Vec4) -> CPUBase (Array n Vec4) -> GL () Source #

GLES => BaseUniform (Array n Vec3) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n Vec3) -> CPUBase (Array n Vec3) -> GL () Source #

GLES => BaseUniform (Array n Vec2) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n Vec2) -> CPUBase (Array n Vec2) -> GL () Source #

GLES => BaseUniform (Array n Int) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n Int) -> CPUBase (Array n Int) -> GL () Source #

GLES => BaseUniform (Array n Bool) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n Bool) -> CPUBase (Array n Bool) -> GL () Source #

GLES => BaseUniform (Array n Float) Source # 

Methods

setUniform :: UniformLocation -> proxy (Array n Float) -> CPUBase (Array n Float) -> GL () Source #

class ShaderType g => BaseAttribute g where Source #

CPU types convertible to GPU types (as attributes).

Minimal complete definition

encodeAttribute, setAttribute

Methods

encodeAttribute :: proxy g -> [CPUBase g] -> GL AnyArray Source #

setAttribute :: proxy g -> GLUInt -> GL () Source #

Instances

GLES => BaseAttribute BVec4 Source # 

Methods

encodeAttribute :: proxy BVec4 -> [CPUBase BVec4] -> GL AnyArray Source #

setAttribute :: proxy BVec4 -> GLUInt -> GL () Source #

GLES => BaseAttribute BVec3 Source # 

Methods

encodeAttribute :: proxy BVec3 -> [CPUBase BVec3] -> GL AnyArray Source #

setAttribute :: proxy BVec3 -> GLUInt -> GL () Source #

GLES => BaseAttribute BVec2 Source # 

Methods

encodeAttribute :: proxy BVec2 -> [CPUBase BVec2] -> GL AnyArray Source #

setAttribute :: proxy BVec2 -> GLUInt -> GL () Source #

GLES => BaseAttribute IVec4 Source # 

Methods

encodeAttribute :: proxy IVec4 -> [CPUBase IVec4] -> GL AnyArray Source #

setAttribute :: proxy IVec4 -> GLUInt -> GL () Source #

GLES => BaseAttribute IVec3 Source # 

Methods

encodeAttribute :: proxy IVec3 -> [CPUBase IVec3] -> GL AnyArray Source #

setAttribute :: proxy IVec3 -> GLUInt -> GL () Source #

GLES => BaseAttribute IVec2 Source # 

Methods

encodeAttribute :: proxy IVec2 -> [CPUBase IVec2] -> GL AnyArray Source #

setAttribute :: proxy IVec2 -> GLUInt -> GL () Source #

GLES => BaseAttribute Vec4 Source # 

Methods

encodeAttribute :: proxy Vec4 -> [CPUBase Vec4] -> GL AnyArray Source #

setAttribute :: proxy Vec4 -> GLUInt -> GL () Source #

GLES => BaseAttribute Vec3 Source # 

Methods

encodeAttribute :: proxy Vec3 -> [CPUBase Vec3] -> GL AnyArray Source #

setAttribute :: proxy Vec3 -> GLUInt -> GL () Source #

GLES => BaseAttribute Vec2 Source # 

Methods

encodeAttribute :: proxy Vec2 -> [CPUBase Vec2] -> GL AnyArray Source #

setAttribute :: proxy Vec2 -> GLUInt -> GL () Source #

GLES => BaseAttribute Int Source # 

Methods

encodeAttribute :: proxy Int -> [CPUBase Int] -> GL AnyArray Source #

setAttribute :: proxy Int -> GLUInt -> GL () Source #

GLES => BaseAttribute Float Source # 

Methods

encodeAttribute :: proxy Float -> [CPUBase Float] -> GL AnyArray Source #

setAttribute :: proxy Float -> GLUInt -> GL () Source #

GLES => BaseAttribute Bool Source # 

Methods

encodeAttribute :: proxy Bool -> [CPUBase Bool] -> GL AnyArray Source #

setAttribute :: proxy Bool -> GLUInt -> GL () Source #

class Generic g => Uniform s g where Source #

Minimal complete definition

withUniforms

Methods

withUniforms :: Applicative f => proxy s -> g -> CPU s g -> (forall g. BaseUniform g => Int -> Proxy g -> CPUBase g -> f ()) -> f () Source #

Instances

(BaseUniform (GCPUValue (Rep g)), Generic g) => Uniform (S * *) g Source # 

Methods

withUniforms :: Applicative f => proxy (S * *) -> g -> CPU (S * *) g -> (forall a. BaseUniform a => Int -> Proxy * a -> CPUBase a -> f ()) -> f () Source #

(GUniformMirror (Rep g) (Rep (CPUMirror g)) (TData (Rep (CPUMirror g))) (TCons (Rep (CPUMirror g))), Generic g, Generic (CPUMirror g)) => Uniform (M * *) g Source # 

Methods

withUniforms :: Applicative f => proxy (M * *) -> g -> CPU (M * *) g -> (forall a. BaseUniform a => Int -> Proxy * a -> CPUBase a -> f ()) -> f () Source #

class Generic g => Attribute s g where Source #

Minimal complete definition

withAttributes

Methods

withAttributes :: Applicative f => proxy s -> g -> [CPU s g] -> (forall g. BaseAttribute g => Int -> Proxy g -> [CPUBase g] -> f ()) -> f () Source #

Instances

(BaseAttribute (GCPUValue (Rep g)), Generic g) => Attribute (S * *) g Source # 

Methods

withAttributes :: Applicative f => proxy (S * *) -> g -> [CPU (S * *) g] -> (forall a. BaseAttribute a => Int -> Proxy * a -> [CPUBase a] -> f ()) -> f () Source #