hylogen-0.1.5.1: GLSL embedded in Haskell

Safe HaskellNone
LanguageHaskell2010

Hylogen.Expr

Description

Internal AST representation.

Synopsis

Documentation

data GLSLType Source #

Internal type tag

Instances

Eq GLSLType Source # 
Ord GLSLType Source # 
Show ExprMono Source # 
Show GLSLType Source # 
MuRef ExprMono Source #

Currently only inlines uniforms.

Associated Types

type DeRef ExprMono :: * -> * #

Methods

mapDeRef :: Applicative f => (forall b. (MuRef b, ((* -> *) ~ DeRef ExprMono) (DeRef b)) => b -> f u) -> ExprMono -> f (DeRef ExprMono u) #

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

data ExprForm Source #

Internal form tag

Instances

Show ExprMono Source # 
Show ExprForm Source # 
MuRef ExprMono Source #

Currently only inlines uniforms.

Associated Types

type DeRef ExprMono :: * -> * #

Methods

mapDeRef :: Applicative f => (forall b. (MuRef b, ((* -> *) ~ DeRef ExprMono) (DeRef b)) => b -> f u) -> ExprMono -> f (DeRef ExprMono u) #

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

data Tree a Source #

Rose tree. Internal AST data structure

Constructors

Tree 

Fields

Instances

Show ExprMono Source # 
MuRef ExprMono Source #

Currently only inlines uniforms.

Associated Types

type DeRef ExprMono :: * -> * #

Methods

mapDeRef :: Applicative f => (forall b. (MuRef b, ((* -> *) ~ DeRef ExprMono) (DeRef b)) => b -> f u) -> ExprMono -> f (DeRef ExprMono u) #

Show a => Show (ExprMonoF a) Source # 
type DeRef ExprMono 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) # 

Methods

pi :: Vec n #

exp :: Vec n -> Vec n #

log :: Vec n -> Vec n #

sqrt :: Vec n -> Vec n #

(**) :: Vec n -> Vec n -> Vec n #

logBase :: Vec n -> Vec n -> Vec n #

sin :: Vec n -> Vec n #

cos :: Vec n -> Vec n #

tan :: Vec n -> Vec n #

asin :: Vec n -> Vec n #

acos :: Vec n -> Vec n #

atan :: Vec n -> Vec n #

sinh :: Vec n -> Vec n #

cosh :: Vec n -> Vec n #

tanh :: Vec n -> Vec n #

asinh :: Vec n -> Vec n #

acosh :: Vec n -> Vec n #

atanh :: Vec n -> Vec n #

log1p :: Vec n -> Vec n #

expm1 :: Vec n -> Vec n #

log1pexp :: Vec n -> Vec n #

log1mexp :: Vec n -> Vec n #

Veccable n => Fractional (Vec n) # 

Methods

(/) :: Vec n -> Vec n -> Vec n #

recip :: Vec n -> Vec n #

fromRational :: Rational -> Vec n #

Veccable n => Num (Vec n) # 

Methods

(+) :: Vec n -> Vec n -> Vec n #

(-) :: Vec n -> Vec n -> Vec n #

(*) :: Vec n -> Vec n -> Vec n #

negate :: Vec n -> Vec n #

abs :: Vec n -> Vec n #

signum :: Vec n -> Vec n #

fromInteger :: Integer -> Vec n #

ToGLSLType ty => Show (Expr ty) Source # 

Methods

showsPrec :: Int -> Expr ty -> ShowS #

show :: Expr ty -> String #

showList :: [Expr ty] -> ShowS #

Veccable n => VectorSpace (Vec n) 

Associated Types

type Scalar (Vec n) :: *

Methods

(*^) :: Scalar (Vec n) -> Vec n -> Vec n

Veccable n => InnerSpace (Vec n) 

Methods

(<.>) :: Vec n -> Vec n -> Scalar (Vec n)

Veccable n => AdditiveGroup (Vec n) 

Methods

zeroV :: Vec n

(^+^) :: Vec n -> Vec n -> Vec n

negateV :: Vec n -> Vec n

(^-^) :: Vec n -> Vec n -> Vec n

((~) * a Vec1, (~) * b Vec1) => ToVec4 (a, b, Vec2) Source # 

Methods

vec4 :: (a, b, Vec2) -> Vec4 Source #

((~) * a Vec1, (~) * c Vec1) => ToVec4 (a, Vec2, c) Source # 

Methods

vec4 :: (a, Vec2, c) -> Vec4 Source #

((~) * b Vec1, (~) * c Vec1) => ToVec4 (Vec2, b, c) Source # 

Methods

vec4 :: (Vec2, b, c) -> Vec4 Source #

type Scalar (Vec n) 
type Scalar (Vec n) = Vec 1

class ToGLSLType ty where Source #

Minimal complete definition

toGLSLType, tag

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

Instances

Functor (TreeF a) Source # 

Methods

fmap :: (a -> b) -> TreeF a a -> TreeF a b #

(<$) :: a -> TreeF a b -> TreeF a a #

Show a => Show (ExprMonoF a) Source # 

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