Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type Shader g i o a = PartialShader g i o a
- type VertexShader g i o = Shader g i (VertexShaderOutput : o) ()
- type FragmentShader g i = Shader g i (FragmentShaderOutput : []) ()
- 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 V2 = V2 Float Float
- data V3 = V3 Float Float Float
- data V4 = V4 Float Float Float Float
- data M2 = M2 V2 V2
- data M3 = M3 V3 V3 V3
- data M4 = M4 V4 V4 V4 V4
- type CFloat = Float
- type CSampler2D = ActiveTexture
- type CV2 = V2
- type CV3 = V3
- type CV4 = V4
- type CM2 = M2
- type CM3 = M3
- type CM4 = M4
- negate :: Float -> Float
- 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
- abs :: Float -> Float
- sign :: Float -> Float
- sqrt :: Float -> Float
- texture2D :: Sampler2D -> V2 -> V4
- (>>=) :: Shader g i o a -> (a -> Shader g i o b) -> Shader g i o b
- (>>) :: Shader g i o a -> Shader g i o b -> Shader g i o b
- fail :: String -> Shader g i o a
- return :: a -> Shader g i o a
- get :: (Member a i, Typeable a, ShaderType a) => Shader g i o a
- global :: (Member a g, Typeable a, ShaderType a) => Shader g i o a
- put :: (Member a o, Typeable a, ShaderType a) => a -> Shader g i o ()
- putVertex :: Member VertexShaderOutput o => V4 -> Shader g i o ()
- putFragment :: Member FragmentShaderOutput o => V4 -> Shader g i o ()
- (.) :: (b -> c) -> (a -> b) -> a -> c
- id :: a -> a
- const :: a -> b -> a
- flip :: (a -> b -> c) -> b -> a -> c
- ($) :: (a -> b) -> a -> b
Documentation
type Shader g i o a = PartialShader g i o a Source
type VertexShader g i o = Shader g i (VertexShaderOutput : o) () Source
type FragmentShader g i = Shader g i (FragmentShaderOutput : []) () Source
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
class Typeable g => UniformCPU c g | g -> c Source
GLES => UniformCPU Float Float | |
GLES => UniformCPU M4 M4 | |
GLES => UniformCPU M3 M3 | |
GLES => UniformCPU M2 M2 | |
GLES => UniformCPU V4 V4 | |
GLES => UniformCPU V3 V3 | |
GLES => UniformCPU V2 V2 | |
GLES => UniformCPU ActiveTexture Sampler2D | |
GLES => UniformCPU CM4 View3 | |
GLES => UniformCPU CM4 Transform3 | |
GLES => UniformCPU CM3 View2 | |
GLES => UniformCPU CM3 Transform2 | |
GLES => UniformCPU CSampler2D Image | |
GLES => UniformCPU CSampler2D Texture2 | |
GLES => UniformCPU CFloat Depth |
class Typeable g => AttributeCPU c g | g -> c Source
GLES => AttributeCPU Float Float | |
GLES => AttributeCPU V4 V4 | |
GLES => AttributeCPU V3 V3 | |
GLES => AttributeCPU V2 V2 | |
GLES => AttributeCPU CV3 Normal3 | |
GLES => AttributeCPU CV3 Position3 | |
GLES => AttributeCPU CV2 UV | |
GLES => AttributeCPU CV2 Position2 | |
GLES => AttributeCPU CV2 UV |
ShaderType V2 | |
Typeable * V2 | |
GLES => AttributeCPU V2 V2 | |
GLES => UniformCPU V2 V2 |
ShaderType V3 | |
Typeable * V3 | |
GLES => AttributeCPU V3 V3 | |
GLES => UniformCPU V3 V3 |
ShaderType V4 | |
Typeable * V4 | |
GLES => AttributeCPU V4 V4 | |
GLES => UniformCPU V4 V4 |
type CSampler2D = ActiveTexture Source
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
putFragment :: Member FragmentShaderOutput o => V4 -> Shader g i o () Source
(.) :: (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