Safe Haskell | None |
---|---|
Language | Haskell2010 |
An example of shader variable:
data Transform2 = Transform2 GMat3 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 (GVec2 x y) :- uv@(UV _) :- N) =
-- Matrix and vector multiplication:
let GVec3 x' y' _ = view .*. trans .* GVec3 x y 1
-- Set of outputs:
in Vertex (GVec4 x' y' z 1) -- Vertex position.
:- uv :- N
- module Data.Boolean
- module Data.VectorSpace
- type Shader gs is os = SVList gs -> SVList is -> SVList os
- type VertexShader g i o = Shader g i (VertexShaderOutput ': o)
- type FragmentShader g i = Shader g i (FragmentShaderOutput ': '[])
- data VertexShaderOutput = Vertex GVec4
- data FragmentShaderOutput
- = Fragment0
- | Fragment GVec4
- | Fragment2 GVec4 GVec4
- | Fragment3 GVec4 GVec4 GVec4
- | Fragment4 GVec4 GVec4 GVec4 GVec4
- | Fragment5 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment6 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment7 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment8 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment9 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment10 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment11 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment12 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment13 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment14 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment15 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- | Fragment16 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4 GVec4
- type ShaderVars = Set ShaderVar
- type VOShaderVars o = (ShaderVars o, ShaderVars (VertexShaderOutput ': o))
- class Generic g => Uniform s g
- class Generic g => Attribute s g
- class Generic a
- data SVList :: [*] -> * where
- data GBool
- data GFloat
- data GInt
- data GSampler2D
- data GSamplerCube
- data GVec2 = GVec2 GFloat GFloat
- data GVec3 = GVec3 GFloat GFloat GFloat
- data GVec4 = GVec4 GFloat GFloat GFloat GFloat
- data GBVec2 = GBVec2 GBool GBool
- data GBVec3 = GBVec3 GBool GBool GBool
- data GBVec4 = GBVec4 GBool GBool GBool GBool
- data GIVec2 = GIVec2 GInt GInt
- data GIVec3 = GIVec3 GInt GInt GInt
- data GIVec4 = GIVec4 GInt GInt GInt GInt
- data GMat2 = GMat2 GVec2 GVec2
- data GMat3 = GMat3 GVec3 GVec3 GVec3
- data GMat4 = GMat4 GVec4 GVec4 GVec4 GVec4
- data GArray n t
- (!) :: (ShaderType t, KnownNat n) => GArray n t -> GInt -> t
- loop :: ShaderType a => Int -> a -> (GInt -> a -> (a, GBool)) -> a
- store :: ShaderType a => a -> a
- texture2D :: GSampler2D -> GVec2 -> GVec4
- texture2DBias :: GSampler2D -> GVec2 -> GFloat -> GVec4
- texture2DProj :: GSampler2D -> GVec3 -> GVec4
- texture2DProjBias :: GSampler2D -> GVec3 -> GFloat -> GVec4
- texture2DProj4 :: GSampler2D -> GVec4 -> GVec4
- texture2DProjBias4 :: GSampler2D -> GVec4 -> GFloat -> GVec4
- texture2DLod :: GSampler2D -> GVec2 -> GFloat -> GVec4
- texture2DProjLod :: GSampler2D -> GVec3 -> GFloat -> GVec4
- texture2DProjLod4 :: GSampler2D -> GVec4 -> GFloat -> GVec4
- arrayLength :: (ShaderType t, KnownNat n) => GArray n t -> GInt
- class Matrix a where
- type Row a = b | b -> a
- class VectorSpace v => Ext v where
- type Extended v = w | w -> v
- minG :: GenTypeGFloat a b => a -> b -> a
- maxG :: GenTypeGFloat a b => a -> b -> a
- modG :: GenType a => a -> a -> a
- floorG :: GenType a => a -> a
- ceilingG :: GenType a => a -> a
- radians :: GenType a => a -> a
- degrees :: GenType a => a -> a
- exp2 :: GenType a => a -> a
- log2 :: GenType a => a -> a
- inversesqrt :: GenType a => a -> a
- fract :: GenType a => a -> a
- clamp :: GenTypeGFloat a b => a -> b -> b -> a
- mix :: GenTypeGFloat a b => a -> a -> b -> a
- step :: GenTypeGFloat a b => b -> a -> a
- smoothstep :: GenTypeGFloat a b => b -> b -> a -> a
- distance :: GenType a => a -> a -> GFloat
- faceforward :: GenType a => a -> a -> a -> a
- reflect :: GenType a => a -> a -> a
- refract :: GenType a => a -> a -> GFloat -> a
- matrixCompMult :: (GMatrix a, GMatrix b, GMatrix c) => a -> b -> c
- class ShaderType a => VecOrd a
- class ShaderType a => VecEq a
- lessThan :: VecOrd a => a -> a -> GBool
- lessThanEqual :: VecOrd a => a -> a -> GBool
- greaterThan :: VecOrd a => a -> a -> GBool
- greaterThanEqual :: VecOrd a => a -> a -> GBool
- equal :: VecEq a => a -> a -> GBool
- notEqual :: VecEq a => a -> a -> GBool
- class ShaderType a => GBoolVector a
- anyBV :: GBoolVector a => a -> GBool
- allBV :: GBoolVector a => a -> GBool
- notBV :: GBoolVector a => a -> GBool
- class ShaderType t => ToGBool t
- bool :: ToGBool t => t -> GBool
- class ShaderType t => ToGInt t
- int :: ToGInt t => t -> GInt
- class ShaderType t => ToGFloat t
- float :: ToGFloat t => t -> GFloat
- position :: GVec4
- fragData :: GArray 16 GVec4
- fragCoord :: GVec4
- fragFrontFacing :: GBool
- data UV = UV GVec2
Documentation
module Data.Boolean
module Data.VectorSpace
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.
data FragmentShaderOutput Source #
The RGBA color of the fragment (1.0 = #FF), or the data of the draw buffers.
type ShaderVars = Set ShaderVar Source #
A type-level set of ShaderVar
s.
type VOShaderVars o = (ShaderVars o, ShaderVars (VertexShaderOutput ': o)) Source #
ShaderVars
for the output of VartexShader
.
Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.
GPU types
A GPU boolean.
A GPU float.
A GPU integer.
A GPU 2D float vector.
A GPU 3D float vector.
A GPU 4D float vector.
A GPU 2D boolean vector.
A GPU 3D boolean vector.
A GPU 4D boolean vector.
A GPU 2D integer vector.
A GPU 3D integer vector.
A GPU 4D integer vector.
A GPU 2x2 float matrix.
A GPU 3x3 float matrix.
A GPU 4x4 float matrix.
GPU functions
store :: ShaderType a => a -> a Source #
Avoid evaluating the expression of the argument more than one time. Conditionals and loops imply it.
texture2DBias :: GSampler2D -> GVec2 -> GFloat -> GVec4 Source #
texture2DProj :: GSampler2D -> GVec3 -> GVec4 Source #
texture2DProjBias :: GSampler2D -> GVec3 -> GFloat -> GVec4 Source #
texture2DProj4 :: GSampler2D -> GVec4 -> GVec4 Source #
texture2DProjBias4 :: GSampler2D -> GVec4 -> GFloat -> GVec4 Source #
texture2DLod :: GSampler2D -> GVec2 -> GFloat -> GVec4 Source #
texture2DProjLod :: GSampler2D -> GVec3 -> GFloat -> GVec4 Source #
texture2DProjLod4 :: GSampler2D -> GVec4 -> GFloat -> GVec4 Source #
Various math functions
class VectorSpace v => Ext v where Source #
(^|) :: v -> Scalar v -> Extended v infixr 5 Source #
Extend the vector with a specified scalar.
(^|^) :: v -> Extended v -> Extended v infixr 5 Source #
Extend the first vector using the components of the second vector.
For instance:
Mat2 (Vec2 x y) (Vec2 z w) ^|^ idmtx =
Mat3 (Vec3 x y 0) (Vec3 z w 0) (Vec3 0 0 1)
extract :: Extended v -> v Source #
Extract a smaller vector.
inversesqrt :: GenType a => a -> a Source #
smoothstep :: GenTypeGFloat a b => b -> b -> a -> a Source #
faceforward :: GenType a => a -> a -> a -> a Source #
matrixCompMult :: (GMatrix a, GMatrix b, GMatrix c) => a -> b -> c Source #
Vector relational functions
lessThanEqual :: VecOrd a => a -> a -> GBool Source #
greaterThan :: VecOrd a => a -> a -> GBool Source #
greaterThanEqual :: VecOrd a => a -> a -> GBool Source #
class ShaderType a => GBoolVector a Source #
anyBV :: GBoolVector a => a -> GBool Source #
allBV :: GBoolVector a => a -> GBool Source #
notBV :: GBoolVector a => a -> GBool Source #
Constructors
Other
fragFrontFacing :: GBool Source #
If the fragment belongs to a front-facing primitive (only works in the fragment shader).