fwgl-0.1.2.2: FRP 2D/3D game engine

Safe HaskellNone
LanguageHaskell2010

FWGL.Graphics.D3

Contents

Description

Simplified 3D graphics system.

Synopsis

Elements

data Element Source

A 3D object with a Texture and a transformation.

cube :: GLES => Texture -> Element Source

A cube with a specified Texture.

Geometry

data Geometry is Source

A set of attributes and indices.

Instances

type Geometry3 = `[Position3, UV, Normal3]` Source

A 3D geometry.

geom :: Texture -> Geometry Geometry3 -> Element Source

An element with a specified Geometry and Texture.

mkGeometry3 Source

Arguments

:: 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

data Texture Source

A texture.

Instances

textureURL Source

Arguments

:: String

URL

-> Texture 

Creates a Texture from an URL or a local file.

colorTex :: GLES => Color -> Texture Source

Generate a 1x1 texture.

mkTexture Source

Arguments

:: GLES 
=> Int

Width.

-> Int

Height.

-> [Color]

List of pixels

-> Texture 

Creates a Texture from a list of pixels.

Transformations

data V3 Source

Three-dimensional vector.

Constructors

V3 !Float !Float !Float 

pos :: V3 -> Element -> Element Source

Translate an Element.

rotX :: Float -> Element -> Element Source

Rotate an Element around the X axis.

rotY :: Float -> Element -> Element Source

Rotate an Element around the X axis.

rotZ :: Float -> Element -> Element Source

Rotate an Element around the X axis.

rotAA :: V3 -> Float -> Element -> Element Source

Rotate an Element around an axis and an angle.

scaleV :: V3 -> Element -> Element Source

Scale an Element in three dimensions.

transform :: M4 -> Element -> Element Source

Transform an Element.

Layers

data Layer Source

An object associated with a program. It can also be a layer included in another.

Element layers

elements :: BackendIO => [Element] -> Layer Source

Create a standard Layer from a list of Elements.

view :: BackendIO => M4 -> [Element] -> Layer Source

Create a Layer from a view matrix and a list of Elements.

Object layers

data Program gs is Source

A vertex shader associated with a compatible fragment shader.

Instances

Eq (Program gs is) 
Hashable (Program gs is) 

layer :: BackendIO => Object DefaultUniforms3D Geometry3 -> Layer Source

Create a Layer from a 3D Object, using the default shader.

layerPrg :: (BackendIO, Subset og pg) => Program pg Geometry3 -> Object og Geometry3 -> Layer Source

Create a Layer from a 3D Object, using a custom shader.

program :: (ValidVertex vgs vis vos, Valid fgs vos [], Equal pgs (Union vgs fgs)) => VertexShader vgs vis vos -> FragmentShader fgs vos -> Program pgs vis Source

Create a Program from the shaders.

Sublayers

subLayer Source

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a Texture.

-> (Texture -> [Layer])

Layer to draw on the screen.

-> Layer 

Use a Layer as a Texture on another.

depthSubLayer Source

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a Texture.

-> (Texture -> [Layer])

Layer to draw on the screen.

-> Layer 

Use the depth Layer as a Texture on another.

Custom 3D objects

data Object gs is Source

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, Objects 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.

object :: BackendIO => M4 -> [Element] -> Object DefaultUniforms3D Geometry3 Source

Create a graphical Object from a list of Elements and a view matrix.

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.

object1Trans :: BackendIO => Element -> Object `[Transform3]` Geometry3 Source

Like object1, but it will only set the transformation matrix.

object1Tex :: BackendIO => Element -> Object `[Texture2]` Geometry3 Source

Like 'object1, but it will only set the texture.

(~~) :: (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 variable (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

data V4 Source

Four-dimensional vector.

Constructors

V4 !Float !Float !Float !Float 

data M4 Source

4x4 matrix.

Constructors

M4 !V4 !V4 !V4 !V4 

mul4 :: M4 -> M4 -> M4 Source

4x4 matrix multiplication.

View matrices

perspectiveMat4 Source

Arguments

:: Float

Far

-> Float

Near

-> Float

FOV

-> Float

Aspect ratio

-> M4 

4x4 perspective projection matrix.

orthoMat4 Source

Arguments

:: Float

Far

-> Float

Near

-> Float

Left

-> Float

Right

-> Float

Bottom

-> Float

Top

-> M4 

4x4 orthographic projection matrix.

cameraMat4 Source

Arguments

:: V3

Eye

-> Float

Pitch

-> Float

Yaw

-> M4 

4x4 FPS camera matrix.

lookAtMat4 :: V3 -> V3 -> V3 -> M4 Source

4x4 "look at" camera matrix.

Transformation matrices

idMat4 :: M4 Source

4x4 identity matrix.

transMat4 :: V3 -> M4 Source

4x4 translation matrix.

rotXMat4 :: Float -> M4 Source

4x4 rotation matrix (X axis).

rotYMat4 :: Float -> M4 Source

4x4 rotation matrix (Y axis).

rotZMat4 :: Float -> M4 Source

4x4 rotation matrix (Z axis).

rotAAMat4 Source

Arguments

:: V3

Axis.

-> Float

Angle

-> M4 

4x4 rotation matrix.

scaleMat4 :: V3 -> M4 Source

4x4 scale matrix.