Safe Haskell | None |
---|---|
Language | Haskell2010 |
An example of shader variable:
newtype Transform2 = Transform2 Mat3
deriving (Typeable,
ShaderType, -- This is a type in the GPU (3x3 matrix).
UniformCPU CMat3) -- This can be used as an uniform
-- and you can set it using a CPU
-- 3x3 matrix
-- (FWGL.Vector.Mat3
)
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 #-}
- type Shader gs is os = STList gs -> STList is -> STList os
- type VertexShader g i o = Shader g i (VertexShaderOutput : o)
- type FragmentShader g i = Shader g i (FragmentShaderOutput : [])
- newtype VertexShaderOutput = Vertex Vec4
- newtype FragmentShaderOutput = Fragment Vec4
- class Typeable a
- class AllTypeable xs
- class ShaderType t
- class Typeable g => UniformCPU c g | g -> c
- class Typeable g => AttributeCPU c g | g -> c
- data Float
- data Sampler2D
- data Vec2 = Vec2 Float Float
- data Vec3 = Vec3 Float Float Float
- data Vec4 = Vec4 Float Float Float Float
- data Mat2 = Mat2 Vec2 Vec2
- data Mat3 = Mat3 Vec3 Vec3 Vec3
- data Mat4 = Mat4 Vec4 Vec4 Vec4 Vec4
- type CFloat = Float
- type CSampler2D = ActiveTexture
- type CVec2 = Vec2
- type CVec3 = Vec3
- type CVec4 = Vec4
- type CMat2 = Mat2
- type CMat3 = Mat3
- type CMat4 = Mat4
- negate :: GenType a => a -> a
- fromInteger :: Integer -> Float
- fromRational :: Rational -> Float
- (*) :: (Mul a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c
- (/) :: (Mul a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c
- (+) :: (Sum a, ShaderType a) => a -> a -> a
- (-) :: (Sum a, ShaderType a) => a -> a -> a
- (^) :: (ShaderType a, ShaderType b) => a -> b -> a
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- (==) :: ShaderType a => a -> a -> Bool
- (>=) :: ShaderType a => a -> a -> Bool
- (<=) :: ShaderType a => a -> a -> Bool
- (<) :: ShaderType a => a -> a -> Bool
- (>) :: ShaderType a => a -> a -> Bool
- ifThenElse :: ShaderType a => Bool -> a -> a -> a
- loop :: ShaderType a => Float -> a -> (Float -> a -> (a, Bool)) -> a
- true :: Bool
- false :: Bool
- store :: ShaderType a => a -> a
- texture2D :: Sampler2D -> Vec2 -> Vec4
- radians :: GenType a => a -> a
- degrees :: GenType a => a -> a
- sin :: GenType a => a -> a
- cos :: GenType a => a -> a
- tan :: GenType a => a -> a
- asin :: GenType a => a -> a
- acos :: GenType a => a -> a
- atan :: GenType a => a -> a
- atan2 :: GenType a => a -> a -> a
- exp :: GenType a => a -> a
- log :: GenType a => a -> a
- exp2 :: GenType a => a -> a
- log2 :: GenType a => a -> a
- sqrt :: GenType a => a -> a
- inversesqrt :: GenType a => a -> a
- abs :: GenType a => a -> a
- sign :: GenType a => a -> a
- floor :: GenType a => a -> a
- ceil :: GenType a => a -> a
- fract :: GenType a => a -> a
- mod :: (GenType a, GenType b) => a -> b -> a
- min :: GenType a => a -> a -> a
- max :: GenType a => a -> a -> a
- clamp :: (GenType a, GenType b) => a -> b -> b -> a
- mix :: (GenType a, GenType b) => a -> a -> b -> a
- step :: GenType a => a -> a -> a
- smoothstep :: (GenType a, GenType b) => b -> b -> a -> a
- length :: GenType a => a -> Float
- distance :: GenType a => a -> a -> Float
- dot :: GenType a => a -> a -> Float
- cross :: Vec3 -> Vec3 -> Vec3
- normalize :: GenType a => a -> a
- faceforward :: GenType a => a -> a -> a -> a
- reflect :: GenType a => a -> a -> a
- refract :: GenType a => a -> a -> Float -> a
- matrixCompMult :: (Matrix a, Matrix b, Matrix c) => a -> b -> c
- position :: Vec4
- fragColor :: Vec4
- data STList :: [*] -> * where
- (.) :: (b -> c) -> (a -> b) -> a -> c
- id :: a -> a
- const :: a -> b -> a
- flip :: (a -> b -> c) -> b -> a -> c
- ($) :: (a -> b) -> a -> b
- fst :: (a, b) -> a
- snd :: (a, b) -> b
Documentation
type Shader gs is os = STList gs -> STList is -> STList os Source
A function from a (heterogeneous) set of uniforms and a set of inputs (attributes or varyings) to a set of outputs (varyings).
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.
newtype VertexShaderOutput Source
The position of the vertex.
newtype FragmentShaderOutput Source
The RGBA color of the fragment (1.0 = #FF).
class Typeable a
The class Typeable
allows a concrete representation of a type to
be calculated.
class AllTypeable xs Source
AllTypeable ([] *) | |
(Typeable * x, AllTypeable xs) => AllTypeable ((:) * x xs) |
class ShaderType t Source
A type in the GPU.
class Typeable g => UniformCPU c g | g -> c Source
CPU types convertible to GPU types (as uniforms).
GLES => UniformCPU Float Float | |
GLES => UniformCPU Vec2 Vec2 | |
GLES => UniformCPU Vec3 Vec3 | |
GLES => UniformCPU Vec4 Vec4 | |
GLES => UniformCPU Mat2 Mat2 | |
GLES => UniformCPU Mat3 Mat3 | |
GLES => UniformCPU Mat4 Mat4 | |
GLES => UniformCPU ActiveTexture Sampler2D | |
GLES => UniformCPU CMat4 View3 | |
GLES => UniformCPU CMat4 Transform3 | |
GLES => UniformCPU CMat3 View2 | |
GLES => UniformCPU CMat3 Transform2 | |
GLES => UniformCPU CSampler2D Image | |
GLES => UniformCPU CSampler2D Texture2 | |
GLES => UniformCPU CFloat Depth |
class Typeable g => AttributeCPU c g | g -> c Source
CPU types convertible to GPU types (as attributes).
GLES => AttributeCPU Float Float | |
GLES => AttributeCPU Vec2 Vec2 | |
GLES => AttributeCPU Vec3 Vec3 | |
GLES => AttributeCPU Vec4 Vec4 | |
GLES => AttributeCPU CVec3 Normal3 | |
GLES => AttributeCPU CVec3 Position3 | |
GLES => AttributeCPU CVec2 UV | |
GLES => AttributeCPU CVec2 Position2 | |
GLES => AttributeCPU CVec2 UV |
A GPU float.
A GPU sampler (sampler2D in GLSL).
A GPU 2D vector.
NB: This is a different type from Data.Vect.Float.Vec2
.
A GPU 3D vector.
A GPU 4D vector.
A GPU 2x2 matrix.
A GPU 3x3 matrix.
A GPU 4x4 matrix.
type CSampler2D = ActiveTexture Source
Samplers in the CPU.
fromInteger :: Integer -> Float Source
fromRational :: Rational -> Float Source
(*) :: (Mul a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c infixl 7 Source
(/) :: (Mul a b c, ShaderType a, ShaderType b, ShaderType c) => a -> b -> c infixl 7 Source
(+) :: (Sum a, ShaderType a) => a -> a -> a infixl 6 Source
(-) :: (Sum a, ShaderType a) => a -> a -> a infixl 6 Source
(^) :: (ShaderType a, ShaderType b) => a -> b -> a infixr 8 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
ifThenElse :: ShaderType a => Bool -> a -> a -> a Source
Rebound if. You don't need to use this function, with -XRebindableSyntax.
:: ShaderType a | |
=> Float | Maximum number of iterations (should be as low as possible, must be an integer literal) |
-> a | Initial value |
-> (Float -> a -> (a, Bool)) | Iteration -> Old value -> (Next, Stop) |
-> a |
store :: ShaderType a => a -> a Source
Avoid executing this expression more than one time. Conditionals and loops imply it.
inversesqrt :: GenType a => a -> a Source
smoothstep :: (GenType a, GenType b) => b -> b -> a -> a Source
faceforward :: GenType a => a -> a -> a -> a Source
matrixCompMult :: (Matrix a, Matrix b, Matrix c) => a -> b -> c Source
data STList :: [*] -> * where Source
An heterogeneous set of ShaderType
s and Typeable
s.
(.) :: (b -> c) -> (a -> b) -> a -> c infixr 9
Function composition.
id :: a -> a
Identity function.
const :: a -> b -> a
Constant function.
flip :: (a -> b -> c) -> b -> a -> c
takes its (first) two arguments in the reverse order of flip
ff
.
($) :: (a -> b) -> a -> b infixr 0
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
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
,
or map
($
0) xs
.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.