ombra-0.2.0.0: Render engine.

Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Shader

Contents

Description

An example of shader variable:

        data Transform2 = Transform2 Mat3 deriving Generic

An example of vertex shader:

        vertexShader :: VertexShader
        -- The types of the uniforms:
                                '[Transform2, View2, Depth]
        -- The types of the attributes:
                                '[Position2, UV]
        -- The types of the varying (outputs), excluding VertexShaderOutput.
                                '[UV]
        vertexShader 
        -- Set of uniforms:
                     (Transform2 trans :- View2 view :- Depth z :- N)
        -- Set of attributes:
                     (Position2 (Vec2 x y) :- uv@(UV _) :- N) =
        -- Matrix and vector multiplication:
                        let Vec3 x' y' _ = view * trans * Vec3 x y 1
        -- Set of outputs:
                        in Vertex (Vec4 x' y' z 1) -- Vertex position.
                           :- uv :- N

Required extensions:

{-# LANGUAGE DataKinds, RebindableSyntax, DeriveDataTypeable,
             GeneralizedNewtypeDeriving, GADTs #-}

Synopsis

Types

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 VertexShader g i o = Shader g i (VertexShaderOutput ': o) Source #

A Shader with a VertexShaderOutput output.

type FragmentShader g i = Shader g i (FragmentShaderOutput ': '[]) Source #

A Shader with only a FragmentShaderOutput output.

data VertexShaderOutput Source #

The position of the vertex.

Constructors

Vertex Vec4 

Instances

Generic VertexShaderOutput Source # 
type Rep VertexShaderOutput Source # 
type Rep VertexShaderOutput = D1 (MetaData "VertexShaderOutput" "Graphics.Rendering.Ombra.Shader.Stages" "ombra-0.2.0.0-8CHCKM67rJ035jbb1iWU9j" False) (C1 (MetaCons "Vertex" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Vec4)))

type ShaderVars = Set ShaderVar Source #

A type-level set of ShaderVars.

type VOShaderVars o = (ShaderVars o, ShaderVars (VertexShaderOutput ': o)) Source #

ShaderVars for the output of VartexShader.

class Generic g => Uniform s g Source #

Minimal complete definition

withUniforms

class Generic g => Attribute s g Source #

Minimal complete definition

withAttributes

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic () 

Associated Types

type Rep () :: * -> * #

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic Void 

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Version 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 

Associated Types

type Rep ExitCode :: * -> * #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All 

Associated Types

type Rep All :: * -> * #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 

Associated Types

type Rep Any :: * -> * #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 

Associated Types

type Rep Associativity :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic VertexShaderOutput # 
Generic UV # 

Associated Types

type Rep UV :: * -> * #

Methods

from :: UV -> Rep UV x #

to :: Rep UV x -> UV #

Generic Normal3 # 

Associated Types

type Rep Normal3 :: * -> * #

Methods

from :: Normal3 -> Rep Normal3 x #

to :: Rep Normal3 x -> Normal3 #

Generic Position3 # 

Associated Types

type Rep Position3 :: * -> * #

Generic View3 # 

Associated Types

type Rep View3 :: * -> * #

Methods

from :: View3 -> Rep View3 x #

to :: Rep View3 x -> View3 #

Generic Transform3 # 

Associated Types

type Rep Transform3 :: * -> * #

Generic Texture2 # 

Associated Types

type Rep Texture2 :: * -> * #

Methods

from :: Texture2 -> Rep Texture2 x #

to :: Rep Texture2 x -> Texture2 #

Generic UV # 

Associated Types

type Rep UV :: * -> * #

Methods

from :: UV -> Rep UV x #

to :: Rep UV x -> UV #

Generic Position2 # 

Associated Types

type Rep Position2 :: * -> * #

Generic View2 # 

Associated Types

type Rep View2 :: * -> * #

Methods

from :: View2 -> Rep View2 x #

to :: Rep View2 x -> View2 #

Generic Transform2 # 

Associated Types

type Rep Transform2 :: * -> * #

Generic Depth # 

Associated Types

type Rep Depth :: * -> * #

Methods

from :: Depth -> Rep Depth x #

to :: Rep Depth x -> Depth #

Generic Image # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

Generic [a] 

Associated Types

type Rep [a] :: * -> * #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a) 

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (V1 p) 

Associated Types

type Rep (V1 p) :: * -> * #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (U1 p) 

Associated Types

type Rep (U1 p) :: * -> * #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (Par1 p) 

Associated Types

type Rep (Par1 p) :: * -> * #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Identity a) 

Associated Types

type Rep (Identity a) :: * -> * #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Generic (Min a) 

Associated Types

type Rep (Min a) :: * -> * #

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Generic (Max a) 

Associated Types

type Rep (Max a) :: * -> * #

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Generic (First a) 

Associated Types

type Rep (First a) :: * -> * #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 

Associated Types

type Rep (Last a) :: * -> * #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (WrappedMonoid m) 

Associated Types

type Rep (WrappedMonoid m) :: * -> * #

Generic (Option a) 

Associated Types

type Rep (Option a) :: * -> * #

Methods

from :: Option a -> Rep (Option a) x #

to :: Rep (Option a) x -> Option a #

Generic (NonEmpty a) 

Associated Types

type Rep (NonEmpty a) :: * -> * #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Generic (Complex a) 

Associated Types

type Rep (Complex a) :: * -> * #

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

Generic (ZipList a) 

Associated Types

type Rep (ZipList a) :: * -> * #

Methods

from :: ZipList a -> Rep (ZipList a) x #

to :: Rep (ZipList a) x -> ZipList a #

Generic (Dual a) 

Associated Types

type Rep (Dual a) :: * -> * #

Methods

from :: Dual a -> Rep (Dual a) x #

to :: Rep (Dual a) x -> Dual a #

Generic (Endo a) 

Associated Types

type Rep (Endo a) :: * -> * #

Methods

from :: Endo a -> Rep (Endo a) x #

to :: Rep (Endo a) x -> Endo a #

Generic (Sum a) 

Associated Types

type Rep (Sum a) :: * -> * #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Generic (Product a) 

Associated Types

type Rep (Product a) :: * -> * #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Generic (First a) 

Associated Types

type Rep (First a) :: * -> * #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 

Associated Types

type Rep (Last a) :: * -> * #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Either a b) 

Associated Types

type Rep (Either a b) :: * -> * #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (Rec1 f p) 

Associated Types

type Rep (Rec1 f p) :: * -> * #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec Char p) 

Associated Types

type Rep (URec Char p) :: * -> * #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p) 

Associated Types

type Rep (URec Double p) :: * -> * #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 

Associated Types

type Rep (URec Float p) :: * -> * #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p) 

Associated Types

type Rep (URec Int p) :: * -> * #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p) 

Associated Types

type Rep (URec Word p) :: * -> * #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (URec (Ptr ()) p) 

Associated Types

type Rep (URec (Ptr ()) p) :: * -> * #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (a, b) 

Associated Types

type Rep (a, b) :: * -> * #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (Arg a b) 

Associated Types

type Rep (Arg a b) :: * -> * #

Methods

from :: Arg a b -> Rep (Arg a b) x #

to :: Rep (Arg a b) x -> Arg a b #

Generic (WrappedMonad m a) 

Associated Types

type Rep (WrappedMonad m a) :: * -> * #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Generic (K1 i c p) 

Associated Types

type Rep (K1 i c p) :: * -> * #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic ((:+:) f g p) 

Associated Types

type Rep ((:+:) f g p) :: * -> * #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic ((:*:) f g p) 

Associated Types

type Rep ((:*:) f g p) :: * -> * #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic ((:.:) f g p) 

Associated Types

type Rep ((:.:) f g p) :: * -> * #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (a, b, c) 

Associated Types

type Rep (a, b, c) :: * -> * #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (WrappedArrow a b c) 

Associated Types

type Rep (WrappedArrow a b c) :: * -> * #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c #

Generic (Const k a b) 

Associated Types

type Rep (Const k a b) :: * -> * #

Methods

from :: Const k a b -> Rep (Const k a b) x #

to :: Rep (Const k a b) x -> Const k a b #

Generic (Alt k f a) 

Associated Types

type Rep (Alt k f a) :: * -> * #

Methods

from :: Alt k f a -> Rep (Alt k f a) x #

to :: Rep (Alt k f a) x -> Alt k f a #

Generic (M1 i c f p) 

Associated Types

type Rep (M1 i c f p) :: * -> * #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic (a, b, c, d) 

Associated Types

type Rep (a, b, c, d) :: * -> * #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (a, b, c, d, e) 

Associated Types

type Rep (a, b, c, d, e) :: * -> * #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (a, b, c, d, e, f) 

Associated Types

type Rep (a, b, c, d, e, f) :: * -> * #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g) 

Associated Types

type Rep (a, b, c, d, e, f, g) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

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

An heterogeneous list of ShaderVars.

Constructors

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

GPU types

data Bool Source #

A GPU boolean.

data Int Source #

A GPU integer.

data Sampler2D Source #

A GPU 2D texture handle.

data SamplerCube Source #

A GPU cube texture handler.

data Vec2 Source #

A GPU 2D float vector. NB: This is a different type from Data.Vect.Float.Vec2.

Constructors

Vec2 Float Float 

data Vec3 Source #

A GPU 3D float vector.

Constructors

Vec3 Float Float Float 

data Vec4 Source #

A GPU 4D float vector.

Constructors

Vec4 Float Float Float Float 

data BVec2 Source #

A GPU 2D boolean vector.

Constructors

BVec2 Bool Bool 

data BVec3 Source #

A GPU 3D boolean vector.

Constructors

BVec3 Bool Bool Bool 

data BVec4 Source #

A GPU 4D boolean vector.

Constructors

BVec4 Bool Bool Bool Bool 

data IVec2 Source #

A GPU 2D integer vector.

Constructors

IVec2 Int Int 

data IVec3 Source #

A GPU 3D integer vector.

Constructors

IVec3 Int Int Int 

data IVec4 Source #

A GPU 4D integer vector.

Constructors

IVec4 Int Int Int Int 

data Mat2 Source #

A GPU 2x2 float matrix.

Constructors

Mat2 Vec2 Vec2 

data Mat3 Source #

A GPU 3x3 float matrix.

Constructors

Mat3 Vec3 Vec3 Vec3 

data Mat4 Source #

A GPU 4x4 float matrix.

Constructors

Mat4 Vec4 Vec4 Vec4 Vec4 

data Array n t Source #

A GPU array.

Functions

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 

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

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

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

Math functions

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 #

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 #

Vector relational functions

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 #

Constructors

class ShaderType t => ToBool t Source #

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

class ShaderType t => ToInt t Source #

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

class ShaderType t => ToFloat t Source #

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

data CompList count Source #

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

Instances

class ToCompList x n | x -> n Source #

Minimal complete definition

toCompList

Instances

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

Methods

toCompList :: t -> CompList n

ToCompList (CompList n) n Source # 

Methods

toCompList :: CompList n -> CompList n

(#) :: (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).

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 #

vec2 :: ToVec2 t => t -> 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 #

vec3 :: ToVec3 t => t -> 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 #

vec4 :: ToVec4 t => t -> Vec4 Source #

class ToBVec2 t where Source #

Minimal complete definition

bvec2

Methods

bvec2 :: t -> BVec2 Source #

Instances

bvec2 :: ToBVec2 t => t -> BVec2 Source #

class ToBVec3 t where Source #

Minimal complete definition

bvec3

Methods

bvec3 :: t -> BVec3 Source #

Instances

bvec3 :: ToBVec3 t => t -> BVec3 Source #

class ToBVec4 t where Source #

Minimal complete definition

bvec4

Methods

bvec4 :: t -> BVec4 Source #

Instances

bvec4 :: ToBVec4 t => t -> BVec4 Source #

class ToIVec2 t where Source #

Minimal complete definition

ivec2

Methods

ivec2 :: t -> IVec2 Source #

Instances

ivec2 :: ToIVec2 t => t -> IVec2 Source #

class ToIVec3 t where Source #

Minimal complete definition

ivec3

Methods

ivec3 :: t -> IVec3 Source #

Instances

ivec3 :: ToIVec3 t => t -> IVec3 Source #

class ToIVec4 t where Source #

Minimal complete definition

ivec4

Methods

ivec4 :: t -> IVec4 Source #

Instances

ivec4 :: ToIVec4 t => t -> IVec4 Source #

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 #

mat2 :: ToMat2 t => t -> 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 #

mat3 :: ToMat3 t => t -> 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 #

mat4 :: ToMat4 t => t -> Mat4 Source #

Operators

(*) :: (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 t, KnownNat n) => Array n t -> Int -> t Source #

Rebinding functions

fromInteger :: Num a => Integer -> a Source #

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

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

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

Prelude functions

(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9 #

Function composition.

id :: a -> a #

Identity function.

const :: a -> b -> a #

const x is a unary function which evaluates to x for all inputs.

For instance,

>>> map (const 42) [0..3]
[42,42,42,42]

flip :: (a -> b -> c) -> b -> a -> c #

flip f takes its (first) two arguments in the reverse order of f.

($) :: (a -> b) -> a -> b infixr 0 #

Application operator. This operator is redundant, since ordinary application (f x) means the same as (f $ x). However, $ has low, right-associative binding precedence, so it sometimes allows parentheses to be omitted; for example:

    f $ g $ h x  =  f (g (h x))

It is also useful in higher-order situations, such as map ($ 0) xs, or zipWith ($) fs xs.

fst :: (a, b) -> a #

Extract the first component of a pair.

snd :: (a, b) -> b #

Extract the second component of a pair.

Variables

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).