Safe Haskell | None |
---|---|
Language | Haskell2010 |
- class ShaderType t where
- data Expr
- data Action
- data ContextVarType
- newtype Float = Float Expr
- newtype Unknown = Unknown Expr
- newtype Sampler2D = Sampler2D Expr
- 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
- fromRational :: Rational -> Float
- fromInteger :: Integer -> Float
- negate :: GenType a => a -> a
- class Mul a b c | a b -> c
- (*) :: (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
- class Sum a
- (+) :: (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
Documentation
class ShaderType t where Source
A type in the GPU.
An expression.
Expressions that are transformed to statements.
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.
fromRational :: Rational -> Float Source
fromInteger :: Integer -> Float Source
class Mul a b c | a b -> c Source
Types that can be multiplied.
Mul Mat4 Mat4 Mat4 | |
Mul Mat4 Vec4 Vec4 | |
Mul Mat4 Float Mat4 | |
Mul Mat3 Mat3 Mat3 | |
Mul Mat3 Vec3 Vec3 | |
Mul Mat3 Float Mat3 | |
Mul Mat2 Mat2 Mat2 | |
Mul Mat2 Vec2 Vec2 | |
Mul Mat2 Float Mat2 | |
Mul Vec4 Mat4 Vec4 | |
Mul Vec4 Vec4 Vec4 | |
Mul Vec4 Float Vec4 | |
Mul Vec3 Mat3 Vec3 | |
Mul Vec3 Vec3 Vec3 | |
Mul Vec3 Float Vec3 | |
Mul Vec2 Mat2 Vec2 | |
Mul Vec2 Vec2 Vec2 | |
Mul Vec2 Float Vec2 | |
Mul Float Mat4 Mat4 | |
Mul Float Mat3 Mat3 | |
Mul Float Mat2 Mat2 | |
Mul Float Vec4 Vec4 | |
Mul Float Vec3 Vec3 | |
Mul Float Vec2 Vec2 | |
Mul Float Float Float |
(*) :: (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
Types that can be added.
(+) :: (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