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

Safe HaskellNone
LanguageHaskell2010

FWGL.Graphics.D2

Contents

Description

Simplified 2D graphics system.

Synopsis

Elements

data Element Source

A 2D object with a Texture, a depth and a transformation.

rect :: GLES => V2 -> Texture -> Element Source

A rectangle with a specified Texture and size.

image Source

Arguments

:: BackendIO 
=> Float

Width.

-> Texture 
-> Element 

A rectangle with the aspect ratio adapted to its texture.

depth :: Float -> Element -> Element Source

Set the depth of an element.

sprite :: BackendIO => Texture -> Element Source

A rectangle with the size and aspect ratio adapted to the screen. You have to use the screenScale view matrix.

Geometry

data Geometry is Source

A set of attributes and indices.

Instances

type Geometry2 = `[Position2, UV]` Source

A 2D geometry.

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

An element with a specified Geometry and Texture.

mkGeometry2 Source

Arguments

:: GLES 
=> [V2]

List of vertices.

-> [V2]

List of UV coordinates.

-> [Word16]

Triangles expressed as triples of indices to the two lists above.

-> Geometry Geometry2 

Create a 2D Geometry. The first two 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 V2 Source

Two-dimensional vector.

Constructors

V2 !Float !Float 

pos :: V2 -> Element -> Element Source

Translate an Element.

rot :: Float -> Element -> Element Source

Rotate an Element.

scaleV :: V2 -> Element -> Element Source

Scale an Element in two dimensions.

transform :: M3 -> 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 => M3 -> [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 DefaultUniforms2D Geometry2 -> Layer Source

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

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

Create a Layer from a 2D 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 2D 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 => M3 -> [Element] -> Object DefaultUniforms2D Geometry2 Source

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

object1 :: BackendIO => Element -> Object `[Image, Depth, Transform2]` Geometry2 Source

Create a graphical Object from a single Element. This lets you set your own globals individually. If the shader uses the view matrix View2 (e.g. the default 2D 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 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 => M3 -> Object gs Geometry2 -> Object (View2 : gs) Geometry2 Source

Set the value of the view matrix of a 2D Object.

type DefaultUniforms2D = Uniforms Source

The uniforms used in the default 2D program.

data Image Source

An uniform that represents the texture used in the default 2D shader.

data Depth Source

An uniform that represents the depth used in the default 2D shader.

data Transform2 Source

An uniform that represents the transformation matrix used in the default 2D shader.

data View2 Source

An uniform that represents the view matrix used in the default 2D shader.

3D matrices

data V3 Source

Three-dimensional vector.

Constructors

V3 !Float !Float !Float 

data M3 Source

3x3 matrix.

Constructors

M3 !V3 !V3 !V3 

mat3 :: (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> M3 Source

Create a 3x3 matrix.

mul3 :: M3 -> M3 -> M3 Source

3x3 matrix multiplication.

Transformation matrices

idMat3 :: M3 Source

The identity 3x3 matrix.

transMat3 :: V2 -> M3 Source

3x3 translation matrix.

rotMat3 :: Float -> M3 Source

3x3 rotation matrix.

scaleMat3 :: V2 -> M3 Source

3x3 scale matrix.