License | BSD3 |
---|---|
Maintainer | ziocroc@gmail.com |
Stability | experimental |
Portability | GHC only |
Safe Haskell | None |
Language | Haskell2010 |
This module exports the shader EDSL.
- module Data.Boolean
- data GBool
- data GFloat
- data GInt
- type TextureSampler = GSampler2D
- 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
- class ShaderType a => GenType a
- type GenTypeGFloat a b = (GenTypeGFloatConstr a b, ShaderType a, ShaderType b)
- data GArray n t
- (!) :: forall t n. (ShaderType t, KnownNat n) => GArray n t -> GInt -> t
- sampleTexture :: TextureSampler -> GVec2 -> GVec4
- sample :: TextureSampler -> GVec2 -> 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
- 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 => a -> a -> a
- 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
Documentation
module Data.Boolean
Types
GPU types
A GPU boolean.
ToGFloat GBool Source # | |
ToGBool GBool Source # | |
ToGInt GBool Source # | |
GLES => GeometryVertex GBool Source # | |
GLES => Uniform GBool Source # | |
ShaderInput GBool Source # | |
MultiShaderType GBool Source # | |
type BooleanOf GBool # | |
data (:->:) GBool # | |
type AttributeTypes GBool Source # | |
type Vertex GBool Source # | |
type CPUUniform GBool Source # | |
type ExprMST GBool Source # | |
A GPU 32-bit float.
ToGFloat GFloat Source # | |
ToGBool GFloat Source # | |
ToGInt GFloat Source # | |
GenType GFloat Source # | |
GLES => GeometryVertex GFloat Source # | |
FragmentShaderOutput GFloat Source # | |
GLES => Uniform GFloat Source # | |
ShaderInput GFloat Source # | |
MultiShaderType GFloat Source # | |
type IntegerOf GFloat # | |
type BooleanOf GFloat # | |
data (:->:) GFloat # | |
type AttributeTypes GFloat Source # | |
type Vertex GFloat Source # | |
type NFloats GFloat Source # | |
type CPUUniform GFloat Source # | |
type ExprMST GFloat Source # | |
A GPU 32-bit integer.
ToGFloat GInt Source # | |
ToGBool GInt Source # | |
ToGInt GInt Source # | |
GLES => GeometryVertex GInt Source # | |
GLES => Uniform GInt Source # | |
ShaderInput GInt Source # | |
MultiShaderType GInt Source # | |
type IntegerOf GInt # | |
type BooleanOf GInt # | |
data (:->:) GInt # | |
type AttributeTypes GInt Source # | |
type Vertex GInt Source # | |
type CPUUniform GInt Source # | |
type ExprMST GInt Source # | |
type TextureSampler = GSampler2D Source #
A GPU 2D float vector.
VecEq GVec2 Source # | |
VecOrd GVec2 Source # | |
GLES => GeometryVertex GVec2 Source # | |
FragmentShaderOutput GVec2 Source # | |
GLES => Uniform GVec2 Source # | |
ShaderInput GVec2 Source # | |
MultiShaderType GVec2 Source # | |
type BooleanOf GVec2 # | |
data (:->:) GVec2 # | |
type Scalar GVec2 # | |
type Extended GVec2 Source # | |
type AttributeTypes GVec2 Source # | |
type Vertex GVec2 Source # | |
type NFloats GVec2 Source # | |
type CPUUniform GVec2 Source # | |
type ExprMST GVec2 Source # | |
A GPU 3D float vector.
VecEq GVec3 Source # | |
VecOrd GVec3 Source # | |
GLES => GeometryVertex GVec3 Source # | |
FragmentShaderOutput GVec3 Source # | |
GLES => Uniform GVec3 Source # | |
ShaderInput GVec3 Source # | |
MultiShaderType GVec3 Source # | |
type BooleanOf GVec3 # | |
data (:->:) GVec3 # | |
type Scalar GVec3 # | |
type Extended GVec3 Source # | |
type AttributeTypes GVec3 Source # | |
type Vertex GVec3 Source # | |
type NFloats GVec3 Source # | |
type CPUUniform GVec3 Source # | |
type ExprMST GVec3 Source # | |
A GPU 4D float vector.
VecEq GVec4 Source # | |
VecOrd GVec4 Source # | |
GLES => GeometryVertex GVec4 Source # | |
FragmentShaderOutput GVec4 Source # | |
GLES => Uniform GVec4 Source # | |
ShaderInput GVec4 Source # | |
MultiShaderType GVec4 Source # | |
GLES => MonadRead GVec4 Draw Source # | |
type BooleanOf GVec4 # | |
data (:->:) GVec4 # | |
type Scalar GVec4 # | |
type AttributeTypes GVec4 Source # | |
type Vertex GVec4 Source # | |
type NFloats GVec4 Source # | |
type CPUUniform GVec4 Source # | |
type ExprMST GVec4 Source # | |
A GPU 2D boolean vector.
A GPU 3D boolean vector.
A GPU 4D boolean vector.
A GPU 2D integer vector.
VecEq GIVec2 Source # | |
VecOrd GIVec2 Source # | |
GLES => GeometryVertex GIVec2 Source # | |
GLES => Uniform GIVec2 Source # | |
ShaderInput GIVec2 Source # | |
MultiShaderType GIVec2 Source # | |
type BooleanOf GIVec2 # | |
data (:->:) GIVec2 # | |
type AttributeTypes GIVec2 Source # | |
type Vertex GIVec2 Source # | |
type CPUUniform GIVec2 Source # | |
type ExprMST GIVec2 Source # | |
A GPU 3D integer vector.
VecEq GIVec3 Source # | |
VecOrd GIVec3 Source # | |
GLES => GeometryVertex GIVec3 Source # | |
GLES => Uniform GIVec3 Source # | |
ShaderInput GIVec3 Source # | |
MultiShaderType GIVec3 Source # | |
type BooleanOf GIVec3 # | |
data (:->:) GIVec3 # | |
type AttributeTypes GIVec3 Source # | |
type Vertex GIVec3 Source # | |
type CPUUniform GIVec3 Source # | |
type ExprMST GIVec3 Source # | |
A GPU 4D integer vector.
VecEq GIVec4 Source # | |
VecOrd GIVec4 Source # | |
GLES => GeometryVertex GIVec4 Source # | |
GLES => Uniform GIVec4 Source # | |
ShaderInput GIVec4 Source # | |
MultiShaderType GIVec4 Source # | |
type BooleanOf GIVec4 # | |
data (:->:) GIVec4 # | |
type AttributeTypes GIVec4 Source # | |
type Vertex GIVec4 Source # | |
type CPUUniform GIVec4 Source # | |
type ExprMST GIVec4 Source # | |
A GPU 2x2 float matrix.
A GPU 3x3 float matrix.
A GPU 4x4 float matrix.
type GenTypeGFloat a b = (GenTypeGFloatConstr a b, ShaderType a, ShaderType b) Source #
A GPU array.
(KnownNat n, ShaderType t, BaseUniform (GArray n t), GLES) => Uniform (GArray n t) Source # | |
(KnownNat n, ShaderType t) => ShaderInput (GArray n t) Source # | |
(KnownNat n, ShaderType t) => MultiShaderType (GArray n t) Source # | |
type BooleanOf (GArray n t) # | |
data (:->:) (GArray n t) # | |
type CPUUniform (GArray n t) Source # | |
type ExprMST (GArray n t) Source # | |
GPU functions
(!) :: forall t n. (ShaderType t, KnownNat n) => GArray n t -> GInt -> t Source #
Access an array element at a given index.
sampleTexture :: TextureSampler -> GVec2 -> GVec4 Source #
Sample a texel from a texture. Sampling in the vertex shader is not supported on some hardware.
sample :: TextureSampler -> GVec2 -> GVec4 Source #
Alias for sampleTexture
.
Various math functions
class VectorSpace v => Ext v where Source #
(^|) :: v -> Scalar v -> Extended v infixl 5 Source #
Extend the vector with a specified scalar.
(^|^) :: v -> Extended v -> Extended v infixl 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.
minG :: GenTypeGFloat a b => a -> b -> a Source #
Faster GPU 'min'/'B.minB'.
maxG :: GenTypeGFloat a b => a -> b -> a Source #
Faster GPU 'max'/'B.maxB'.
inversesqrt :: GenType a => a -> a Source #
clamp :: GenTypeGFloat a b => a -> b -> b -> a Source #
mix :: GenTypeGFloat a b => a -> a -> b -> a Source #
Linear interpolation between two values.
mix x y t = x*(1-t) + y*t
step :: GenTypeGFloat a b => b -> a -> a Source #
step e x
returns 0 if x < e, 1 otherwise.
faceforward :: GenType a => a -> a -> a -> a Source #
matrixCompMult :: GMatrix a => a -> a -> a Source #
Component-wise multiplication of matrices.
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 #