Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Object gs is
- (~~) :: (Equal gs gs', Equal is is') => Object gs is -> Object gs' is' -> Object (Union gs gs') (Union is is')
- unsafeJoin :: (Equal gs'' (Union gs gs'), Equal is'' (Union is is')) => Object gs is -> Object gs' is' -> Object gs'' is''
- nothing :: Object [] []
- geom :: Geometry i -> Object [] i
- data Program gs is
- program :: (ValidVertex vgs vis vos, Valid fgs vos [], Equal pgs (Union vgs fgs)) => VertexShader vgs vis vos -> FragmentShader fgs vos -> Program pgs vis
- global :: (Typeable g, UniformCPU c g) => g -> c -> Object gs is -> Object (g : gs) is
- globalDraw :: (Typeable g, UniformCPU c g) => g -> Draw c -> Object gs is -> Object (g : gs) is
- globalTexture :: (BackendIO, Typeable g, UniformCPU ActiveTexture g) => g -> Texture -> Object gs is -> Object (g : gs) is
- globalTexSize :: (BackendIO, Typeable g, UniformCPU c g) => g -> Texture -> ((Int, Int) -> c) -> Object gs is -> Object (g : gs) is
- data Layer
- layer :: (Subset oi pi, Subset og pg) => Program pg pi -> Object og oi -> Layer
- subLayer :: Int -> Int -> Layer -> (Texture -> [Layer]) -> Layer
- depthSubLayer :: Int -> Int -> Layer -> (Texture -> [Layer]) -> Layer
- data Geometry is
- data AttrList is where
- AttrListNil :: AttrList []
- AttrListCons :: (Hashable c, AttributeCPU c g) => g -> [c] -> AttrList gs -> AttrList (g : gs)
- mkGeometry :: GLES => AttrList is -> [Word16] -> Geometry is
- data Texture
- mkTexture :: GLES => Int -> Int -> [Color] -> Texture
- textureURL :: String -> Texture
- textureFile :: String -> Texture
- data Color = Color !Word8 !Word8 !Word8 !Word8
- colorTex :: GLES => Color -> Texture
- module FWGL.Vector
Documentation
data Object gs is
An object is a set of geometries associated with some uniforms. For
example, if you want to draw a rotating cube, its vertices, normals, etc.
would be the Geometry
, the combination of the geometry and the value of the
model matrix would be the Object
, and the combination of the object with
a Program
would be the Layer
. In fact, Object
s are just descriptions
of the actions to perform to draw something. Instead, the Element types in
FWGL.Graphics.D2 and FWGL.Graphics.D3 represent managed (high level) objects,
and they are ultimately converted to them.
(~~) :: (Equal gs gs', Equal is is') => Object gs is -> Object gs' is' -> Object (Union gs gs') (Union is is')
Join two objects.
unsafeJoin :: (Equal gs'' (Union gs gs'), Equal is'' (Union is is')) => Object gs is -> Object gs' is' -> Object gs'' is''
Join two objects, even if they don't provide the same variables.
data Program gs is
A vertex shader associated with a compatible fragment shader.
program :: (ValidVertex vgs vis vos, Valid fgs vos [], Equal pgs (Union vgs fgs)) => VertexShader vgs vis vos -> FragmentShader fgs vos -> Program pgs vis
Create a Program
from the shaders.
global :: (Typeable g, UniformCPU c g) => g -> c -> Object gs is -> Object (g : gs) is
Sets a global variable (uniform) of an object.
globalDraw :: (Typeable g, UniformCPU c g) => g -> Draw c -> Object gs is -> Object (g : gs) is
Sets a global (uniform) of an object using the Draw
monad.
globalTexture :: (BackendIO, Typeable g, UniformCPU ActiveTexture g) => g -> Texture -> Object gs is -> Object (g : gs) is
Sets a global (uniform) of an object using a Texture
.
globalTexSize :: (BackendIO, Typeable g, UniformCPU c g) => g -> Texture -> ((Int, Int) -> c) -> Object gs is -> Object (g : gs) is
Sets a global (uniform) of an object using the dimensions of a Texture
.
data Layer
An object associated with a program. It can also be a layer included in another.
layer :: (Subset oi pi, Subset og pg) => Program pg pi -> Object og oi -> Layer
Associate an object with a program.
data AttrList is where
AttrListNil :: AttrList [] | |
AttrListCons :: (Hashable c, AttributeCPU c g) => g -> [c] -> AttrList gs -> AttrList (g : gs) |
Creates a Texture
from a list of pixels.
textureFile :: String -> Texture
The same as textureURL
.
data Color
An RGBA 32-bit color.
module FWGL.Vector