Safe Haskell | None |
---|---|
Language | Haskell2010 |
Simplified 3D graphics system.
- data Element
- cube :: GLES => Texture -> Element
- data Geometry is
- type Geometry3 = `[Position3, UV, Normal3]`
- geom :: Texture -> Geometry Geometry3 -> Element
- mkGeometry3 :: GLES => [V3] -> [V2] -> [V3] -> [Word16] -> Geometry Geometry3
- module FWGL.Graphics.Color
- data Texture
- textureURL :: String -> Texture
- textureFile :: String -> Texture
- textureLayer :: GLES => Int -> Int -> Layer -> Texture
- colorTex :: GLES => Color -> Texture
- mkTexture :: GLES => Int -> Int -> [Color] -> Texture
- data V3 = V3 !Float !Float !Float
- pos :: V3 -> Element -> Element
- rotX :: Float -> Element -> Element
- rotY :: Float -> Element -> Element
- rotZ :: Float -> Element -> Element
- rotAA :: V3 -> Float -> Element -> Element
- scale :: Float -> Element -> Element
- scaleV :: V3 -> Element -> Element
- transform :: M4 -> Element -> Element
- data Layer
- elements :: BackendIO => [Element] -> Layer
- view :: BackendIO => M4 -> [Element] -> Layer
- layer :: BackendIO => Object DefaultUniforms3D Geometry3 -> Layer
- layerPrg :: (BackendIO, Subset og pg) => Program pg Geometry3 -> Object og Geometry3 -> Layer
- data Object gs is
- object :: BackendIO => M4 -> [Element] -> Object DefaultUniforms3D Geometry3
- object1 :: BackendIO => Element -> Object `[Transform3, Texture2]` Geometry3
- (~~) :: (Equal gs gs', Equal is is') => Object gs is -> Object gs' is' -> Object (Union gs gs') (Union is is')
- global :: (Typeable g, UniformCPU c g) => g -> 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
- viewObject :: BackendIO => M4 -> Object gs Geometry3 -> Object (View3 : gs) Geometry3
- type DefaultUniforms3D = Uniforms
- data Texture2
- data Transform3
- data View3
- data V4 = V4 !Float !Float !Float !Float
- data M4 = M4 !V4 !V4 !V4 !V4
- mat4 :: (Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float) -> M4
- mul4 :: M4 -> M4 -> M4
- perspectiveMat4 :: Float -> Float -> Float -> Float -> M4
- idMat4 :: M4
- transMat4 :: V3 -> M4
- rotXMat4 :: Float -> M4
- rotYMat4 :: Float -> M4
- rotZMat4 :: Float -> M4
- rotAAMat4 :: V3 -> Float -> M4
- scaleMat4 :: V3 -> M4
Elements
Geometry
:: GLES | |
=> [V3] | List of vertices. |
-> [V2] | List of UV coordinates. |
-> [V3] | List of normals. |
-> [Word16] | Triangles expressed as triples of indices to the three lists above. |
-> Geometry Geometry3 |
Create a 3D Geometry
. The first three lists should have the same length.
Textures
module FWGL.Graphics.Color
textureFile :: String -> Texture Source
Creates a Texture
from a file (Desktop only).
Creates a Texture
from a list of pixels.
Transformations
Three-dimensional vector.
Layers
Element layers
Object layers
layerPrg :: (BackendIO, Subset og pg) => Program pg Geometry3 -> Object og Geometry3 -> Layer Source
Custom 3D objects
object1 :: BackendIO => Element -> Object `[Transform3, Texture2]` Geometry3 Source
Create a graphical Object
from a single Element
. This lets you set your
own globals individually. If the shader uses the view matrix View3
(e.g.
the default 3D shader), you have to set it with viewObject
.
(~~) :: (Equal gs gs', Equal is is') => Object gs is -> Object gs' is' -> Object (Union gs gs') (Union is is') Source
Join two objects.
Globals
global :: (Typeable g, UniformCPU c g) => g -> c -> Object gs is -> Object (g : gs) is Source
Sets a global (uniform) of an object.
globalTexture :: (BackendIO, Typeable g, UniformCPU ActiveTexture g) => g -> Texture -> Object gs is -> Object (g : gs) is Source
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 Source
Sets a global (uniform) of an object using the dimensions of a Texture
.
viewObject :: BackendIO => M4 -> Object gs Geometry3 -> Object (View3 : gs) Geometry3 Source
Set the value of the view matrix of a 3D Object
.
type DefaultUniforms3D = Uniforms Source
The uniforms used in the default 3D program.
3D matrices
Four-dimensional vector.
4x4 matrix.
Eq M4 | |
Show M4 | |
GLES => UniformCPU M4 M4 | |
GLES => UniformCPU CM4 View3 | |
GLES => UniformCPU CM4 Transform3 |
mat4 :: (Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float, Float) -> M4 Source
Create a 4x4 matrix.
View matrices
4x4 perspective matrix.