hylogen-0.1.3.2: an EDSL for live-coding fragment shaders

Safe HaskellNone
LanguageHaskell2010

Hylogen.Expr

Description

Internal AST representation.

Synopsis

Documentation

data ExprForm Source

Internal form tag

Instances

data Tree a Source

Rose tree. Internal AST data structure

Constructors

Tree 

Fields

getElem :: a
 
getChildren :: [Tree a]
 

Instances

Show ExprMono Source 
MuRef ExprMono Source

Currently only inlines uniforms.

Show a => Show (ExprMonoF a) Source 
type DeRef ExprMono = ExprMonoF Source 

type ExprMono = Tree (ExprForm, GLSLType, String) Source

Untyped Expr representation Carries type information in type tag

data Expr ty Source

Light type wrapper

Note the internal type tag is not directly dependent on the actual type!

We use the ToGLSLType typeclass to genenerate dependence from types to values

Constructors

Expr 

Instances

Num Booly

We use Num operators for Boolean arithmetic:

Veccable n => Floating (Vec n) 
Veccable n => Fractional (Vec n) 
Veccable n => Num (Vec n) 
ToGLSLType ty => Show (Expr ty) Source 
Veccable n => VectorSpace (Vec n) 
Veccable n => InnerSpace (Vec n) 
Veccable n => AdditiveGroup (Vec n) 
((~) * a Vec1, (~) * b Vec1) => ToVec4 (a, b, Vec2) Source 
((~) * a Vec1, (~) * c Vec1) => ToVec4 (a, Vec2, c) Source 
((~) * b Vec1, (~) * c Vec1) => ToVec4 (Vec2, b, c) Source 
type Scalar (Vec n) = Vec 1 

class ToGLSLType ty where Source

Methods

toGLSLType :: ty -> GLSLType Source

Gives us dependence from typed singleton tags to untyped tags

tag :: ty Source

Singleton tag

uniform :: forall a. ToGLSLType a => String -> Expr a Source

Uniform expression.

op1 :: forall a b. (ToGLSLType a, ToGLSLType b) => String -> Expr a -> Expr b Source

Unary operator. Most generally typed.

op1'' :: forall a. ToGLSLType a => String -> Expr a -> Expr a Source

Unary operator. Input and output values have the same type.

op1pre :: forall a b. (ToGLSLType a, ToGLSLType b) => String -> Expr a -> Expr b Source

Unary operator. Prefix function call style. Most generally typed.

op1pre'' :: forall a. ToGLSLType a => String -> Expr a -> Expr a Source

Unary operator. Prefix function call style. Input and output values have the same type.

op2 :: forall a b c. (ToGLSLType a, ToGLSLType b, ToGLSLType c) => String -> Expr a -> Expr b -> Expr c Source

Binary operator. Most generally typed.

op2' :: forall a c. (ToGLSLType a, ToGLSLType c) => String -> Expr a -> Expr a -> Expr c Source

Binary operator. Arguments have the same type.

op2'' :: forall a. ToGLSLType a => String -> Expr a -> Expr a -> Expr a Source

Binary operator. Input and output values have the same type.

op2pre :: forall a b c. (ToGLSLType a, ToGLSLType b, ToGLSLType c) => String -> Expr a -> Expr b -> Expr c Source

Binary operator. Prefix function call style. Most generally typed.

op2pre' :: forall a c. (ToGLSLType a, ToGLSLType c) => String -> Expr a -> Expr a -> Expr c Source

Binary operator. Prefix function call style. Arguments have the same type.

op2pre'' :: forall a. ToGLSLType a => String -> Expr a -> Expr a -> Expr a Source

Binary operator. Prefix function call style. Input and output values have the same type.

op3pre :: forall a b c d. (ToGLSLType a, ToGLSLType b, ToGLSLType c, ToGLSLType d) => String -> Expr a -> Expr b -> Expr c -> Expr d Source

Ternary operator. Prefix function call style. Most generally typed.

op3pre' :: forall a d. (ToGLSLType a, ToGLSLType d) => String -> Expr a -> Expr a -> Expr a -> Expr d Source

Ternary operator. Prefix function call style. Arguments have the same type.

op3pre'' :: forall a. ToGLSLType a => String -> Expr a -> Expr a -> Expr a -> Expr a Source

Ternary operator. Prefix function call style. Input and output values have the same type.

op4pre :: forall a b c d e. (ToGLSLType a, ToGLSLType b, ToGLSLType c, ToGLSLType d, ToGLSLType e) => String -> Expr a -> Expr b -> Expr c -> Expr d -> Expr e Source

Quaternary operator. Prefix function call style. Most generally typed.

op4pre' :: forall a e. (ToGLSLType a, ToGLSLType e) => String -> Expr a -> Expr a -> Expr a -> Expr a -> Expr e Source

Quaternary operator. Prefix function call style. Arguments have the same type.

op4pre'' :: forall a e. (ToGLSLType a, ToGLSLType e) => String -> Expr a -> Expr a -> Expr a -> Expr a -> Expr e Source

Quaternary operator. Prefix function call style. Input and output values have the same type.

data TreeF a b Source

Open tree type, to be used for explicit recursion with data-reify for preserving sharing.

Note the second argument of the constructor is a list of Maybe b's. We use Maybe's to determine whether or not a child expression gets inlined.

Constructors

TreeF 

Fields

getElemF :: a
 
getChildrenF :: [Maybe b]
 

Instances

type ExprMonoF = TreeF (ExprForm, GLSLType, String, [ExprMono]) Source

Open untyped expression representation, to be used for explicit recursion with data-reify for preserving sharing.

Note the presence of a list of closed ExprMono's in the tuple. We use this list to recover unshared child expressions when they need to be inlined.

emfStringAt :: Show a => ExprMonoF a -> Int -> String Source

Returns the string representation of the nth child of an open untyped expression, accounting for inlining