ombra-0.1.1.0: Render engine.

Safe HaskellSafe
LanguageHaskell2010

Graphics.Rendering.Ombra.Shader.Language.Functions

Synopsis

Documentation

class (Base a aBase, Base b bBase) => Arithmetic aBase bBase a b result | a b -> result, b -> aBase bBase, a -> aBase bBase, result -> aBase bBase Source #

class (Base a aBase, Base b bBase) => Mul aBase bBase a b result | a b -> result, b -> aBase bBase, a -> aBase bBase, result -> aBase bBase Source #

Types that can be multiplied.

class ShaderType a => GenType a Source #

Floats or vectors.

Instances

type family GenTypeFloatConstr a b where ... Source #

(*) :: (Mul aBase bBase a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c infixl 7 Source #

(/) :: (Arithmetic aBase bBase a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c infixl 7 Source #

(+) :: (Arithmetic aBase bBase a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c infixl 6 Source #

(-) :: (Arithmetic aBase bBase a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c infixl 6 Source #

(^) :: (ShaderType a, GenType a) => a -> a -> a infixr 8 Source #

(&&) :: Bool -> Bool -> Bool infixr 3 Source #

(||) :: Bool -> Bool -> Bool infixr 2 Source #

(==) :: ShaderType a => a -> a -> Bool infix 4 Source #

(/=) :: ShaderType a => a -> a -> Bool infix 4 Source #

(>=) :: ShaderType a => a -> a -> Bool infix 4 Source #

(<=) :: ShaderType a => a -> a -> Bool infix 4 Source #

(<) :: ShaderType a => a -> a -> Bool infix 4 Source #

(>) :: ShaderType a => a -> a -> Bool infix 4 Source #

lessThan :: VecOrd a => a -> a -> Bool Source #

lessThanEqual :: VecOrd a => a -> a -> Bool Source #

greaterThan :: VecOrd a => a -> a -> Bool Source #

greaterThanEqual :: VecOrd a => a -> a -> Bool Source #

equal :: VecEq a => a -> a -> Bool Source #

notEqual :: VecEq a => a -> a -> Bool Source #

anyB :: BoolVector a => a -> Bool Source #

allB :: BoolVector a => a -> Bool Source #

notB :: BoolVector a => a -> Bool Source #

negate :: GenType a => a -> a Source #

not :: GenType a => a -> a Source #

class (ShaderType a, Base a a) => Num a where Source #

Minimal complete definition

fromInteger

Methods

fromInteger :: Integer -> a Source #

radians :: GenType a => a -> a Source #

degrees :: GenType a => a -> a Source #

sin :: GenType a => a -> a Source #

cos :: GenType a => a -> a Source #

tan :: GenType a => a -> a Source #

asin :: GenType a => a -> a Source #

acos :: GenType a => a -> a Source #

atan :: GenType a => a -> a Source #

atan2 :: GenType a => a -> a -> a Source #

exp :: GenType a => a -> a Source #

log :: GenType a => a -> a Source #

exp2 :: GenType a => a -> a Source #

log2 :: GenType a => a -> a Source #

sqrt :: GenType a => a -> a Source #

inversesqrt :: GenType a => a -> a Source #

abs :: GenType a => a -> a Source #

sign :: GenType a => a -> a Source #

floor :: GenType a => a -> a Source #

ceil :: GenType a => a -> a Source #

fract :: GenType a => a -> a Source #

mod :: GenTypeFloat a b => a -> b -> a Source #

min :: GenTypeFloat a b => a -> b -> a Source #

max :: GenTypeFloat a b => a -> b -> a Source #

clamp :: GenTypeFloat a b => a -> b -> b -> a Source #

mix :: GenTypeFloat a b => a -> a -> b -> a Source #

step :: GenTypeFloat a b => b -> a -> a Source #

smoothstep :: GenTypeFloat a b => b -> b -> a -> a Source #

length :: GenType a => a -> Float Source #

(!) :: (ShaderType t, KnownNat n) => Array n t -> Int -> t Source #

distance :: GenType a => a -> a -> Float Source #

dot :: GenType a => a -> a -> Float Source #

normalize :: GenType a => a -> a Source #

faceforward :: GenType a => a -> a -> a -> a Source #

reflect :: GenType a => a -> a -> a Source #

refract :: GenType a => a -> a -> Float -> a Source #

matrixCompMult :: (Matrix a, Matrix b, Matrix c) => a -> b -> c Source #

store :: ShaderType a => a -> a Source #

Avoid evaluating the expression of the argument more than one time. Conditionals and loops imply it.

ifThenElse :: ShaderType a => Bool -> a -> a -> a Source #

Rebound if. You don't need to use this function, with -XRebindableSyntax.

loop Source #

Arguments

:: ShaderType a 
=> Int

Maximum number of iterations (should be as low as possible, must be an integer literal)

-> a

Initial value

-> (Int -> a -> (a, Bool))

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

-> a 

position :: Vec4 Source #

The position of the vertex (only works in the vertex shader).

fragData :: Array 16 Vec4 Source #

The data of the fragment (only works in the fragment shader).

fragCoord :: Vec4 Source #

The coordinates of the fragment (only works in the fragment shader).

fragFrontFacing :: Bool Source #

If the fragment belongs to a front-facing primitive (only works in the fragment shader).

int :: ToInt t => t -> Int Source #

bool :: ToBool t => t -> Bool Source #

float :: ToFloat t => t -> Float Source #

class ToVec2 t where Source #

Minimal complete definition

vec2

Methods

vec2 :: t -> Vec2 Source #

Instances

((<=) (Components Vec2) n, ToCompList t n) => ToVec2 t Source # 

Methods

vec2 :: t -> Vec2 Source #

ToVec2 Float Source # 

Methods

vec2 :: Float -> Vec2 Source #

class ToVec3 t where Source #

Minimal complete definition

vec3

Methods

vec3 :: t -> Vec3 Source #

Instances

((<=) (Components Vec3) n, ToCompList t n) => ToVec3 t Source # 

Methods

vec3 :: t -> Vec3 Source #

ToVec3 Float Source # 

Methods

vec3 :: Float -> Vec3 Source #

class ToVec4 t where Source #

Minimal complete definition

vec4

Methods

vec4 :: t -> Vec4 Source #

Instances

((<=) (Components Vec4) n, ToCompList t n) => ToVec4 t Source # 

Methods

vec4 :: t -> Vec4 Source #

ToVec4 Float Source # 

Methods

vec4 :: Float -> Vec4 Source #

class ToIVec2 t where Source #

Minimal complete definition

ivec2

Methods

ivec2 :: t -> IVec2 Source #

Instances

class ToIVec3 t where Source #

Minimal complete definition

ivec3

Methods

ivec3 :: t -> IVec3 Source #

Instances

class ToIVec4 t where Source #

Minimal complete definition

ivec4

Methods

ivec4 :: t -> IVec4 Source #

Instances

class ToBVec2 t where Source #

Minimal complete definition

bvec2

Methods

bvec2 :: t -> BVec2 Source #

Instances

class ToBVec3 t where Source #

Minimal complete definition

bvec3

Methods

bvec3 :: t -> BVec3 Source #

Instances

class ToBVec4 t where Source #

Minimal complete definition

bvec4

Methods

bvec4 :: t -> BVec4 Source #

Instances

class ToMat2 t where Source #

Minimal complete definition

mat2

Methods

mat2 :: t -> Mat2 Source #

Instances

((<=) (Components Mat2) n, ToCompList t n) => ToMat2 t Source # 

Methods

mat2 :: t -> Mat2 Source #

ToMat2 Float Source # 

Methods

mat2 :: Float -> Mat2 Source #

class ToMat3 t where Source #

Minimal complete definition

mat3

Methods

mat3 :: t -> Mat3 Source #

Instances

((<=) (Components Mat3) n, ToCompList t n) => ToMat3 t Source # 

Methods

mat3 :: t -> Mat3 Source #

ToMat3 Float Source # 

Methods

mat3 :: Float -> Mat3 Source #

class ToMat4 t where Source #

Minimal complete definition

mat4

Methods

mat4 :: t -> Mat4 Source #

Instances

((<=) (Components Mat4) n, ToCompList t n) => ToMat4 t Source # 

Methods

mat4 :: t -> Mat4 Source #

ToMat4 Float Source # 

Methods

mat4 :: Float -> Mat4 Source #

data CompList count where Source #

Useful type for constructing vectors and matrices from scalars, vectors and matrices.

Constructors

CL :: (1 <= Components t, ShaderType t) => t -> CompList (Components t) 
CLAppend :: CompList x -> CompList y -> CompList (x + y) 

Instances

class ToCompList x n | x -> n where Source #

Minimal complete definition

toCompList

Methods

toCompList :: x -> CompList n Source #

Instances

((<=) 1 n, ShaderType t, (~) Nat n (Components t)) => ToCompList t n Source # 

Methods

toCompList :: t -> CompList n Source #

ToCompList (CompList n) n Source # 

(#) :: (ToCompList x xn, ToCompList y yn) => x -> y -> CompList (xn + yn) infixr 5 Source #

You can call *vec* and mat* with a single scalar or with a CompList containing enough components. This function helps you create CompLists.

Examples:

vec2 0
mat2 $ Vec2 2 4 # Vec2 1 3
vec4 $ mat2 (0 # 1 # vec2 2) # 9  -- 9 is discarded
mat4 $ 5 # vec2 5 # Vec3 1 2 3 # Mat2 (vec2 0) (Vec2 1 2) # mat3 0
vec4 $ 1 # vec2 0 -- Not enough components, fails with "Couldn't match type
                  -- ‘'Prelude.False’ with 'Prelude.True’" (because
                  -- Components Vec4 <=? 3 ~ False).

op1 :: (ShaderType a, ShaderType b) => String -> a -> b Source #

op2 :: (ShaderType a, ShaderType b, ShaderType c) => String -> a -> b -> c Source #

fun1 :: (ShaderType a, ShaderType b) => String -> a -> b Source #

fun2 :: (ShaderType a, ShaderType b, ShaderType c) => String -> a -> b -> c Source #

fun3 :: (ShaderType a, ShaderType b, ShaderType c, ShaderType d) => String -> a -> b -> c -> d Source #

funCompList :: (ToCompList cl n, ShaderType r) => String -> cl -> r Source #