ombra-0.1.1.0: Render engine.

Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Shader.ShaderVar

Synopsis

Documentation

type Shader gs is os = SVList gs -> SVList is -> SVList os Source #

A function from a set of uniforms and a set of inputs (attributes or varyings) to a set of outputs (varyings). It can be used to represent a reusable piece of shader code, other than actual shaders.

type Member x xs = IsMember x xs ~ True Source #

type Subset xs ys = TrueOrErr (IsSubset xs ys) ((((Text "\8216" :<>: ShowType xs) :<>: Text "\8217 is not a subset of \8216") :<>: ShowType ys) :<>: Text "\8217") Source #

type Equal xs ys = IsEqual xs ys ~ True Source #

type family Union (xs :: [*]) (ys :: [*]) where ... Source #

Equations

Union '[] ys = ys 
Union (x ': xs) ys = Union xs (Insert x ys) 

type family Insert y (xs :: [*]) where ... Source #

Equations

Insert y '[] = '[y] 
Insert y (y ': xs) = y ': xs 
Insert y (x ': xs) = x ': Insert y xs 

data SVList :: [*] -> * where Source #

An heterogeneous list of ShaderVars.

Constructors

N :: SVList '[] 
(:-) :: ShaderVar a => a -> SVList xs -> SVList (a ': xs) infixr 4 

class ShaderVar g where Source #

Minimal complete definition

varPreName, varBuild, varToList

Methods

varPreName :: g -> String Source #

varBuild :: (forall x. ShaderType x => Int -> x) -> Proxy g -> g Source #

varToList :: (forall x. ShaderType x => Int -> x -> t) -> g -> [t] Source #

Instances

(GShaderVar (Rep g), Generic g) => ShaderVar g Source # 

Methods

varPreName :: g -> String Source #

varBuild :: (forall x. ShaderType x => Int -> x) -> Proxy * g -> g Source #

varToList :: (forall x. ShaderType x => Int -> x -> t) -> g -> [t] Source #

ShaderVar FragmentShaderOutput Source # 

type ShaderVars = Set ShaderVar Source #

A type-level set of ShaderVars.

type BaseTypes g = GBaseTypes (Rep g) Source #

varBuild :: ShaderVar g => (forall x. ShaderType x => Int -> x) -> Proxy g -> g Source #

varToList :: ShaderVar g => (forall x. ShaderType x => Int -> x -> t) -> g -> [t] Source #

svFold :: (forall x. ShaderVar x => acc -> x -> acc) -> acc -> SVList xs -> acc Source #

svToList :: (forall x. ShaderVar x => x -> [y]) -> SVList xs -> [y] Source #

staticSVList :: ShaderVars xs => Proxy (xs :: [*]) -> (forall x. ShaderVar x => Proxy x -> x) -> SVList xs Source #

Create a SVList with a function.