Safe Haskell | None |
---|---|
Language | Haskell2010 |
Simplified 2D graphics system.
- data Element
- rect :: GLES => V2 -> Texture -> Element
- image :: BackendIO => Float -> Texture -> Element
- depth :: Float -> Element -> Element
- sprite :: BackendIO => Texture -> Element
- data Geometry is
- type Geometry2 = `[Position2, UV]`
- geom :: Texture -> Geometry Geometry2 -> Element
- mkGeometry2 :: GLES => [V2] -> [V2] -> [Word16] -> Geometry Geometry2
- module FWGL.Graphics.Color
- data Texture
- textureURL :: String -> Texture
- textureFile :: String -> Texture
- colorTex :: GLES => Color -> Texture
- mkTexture :: GLES => Int -> Int -> [Color] -> Texture
- data V2 = V2 !Float !Float
- pos :: V2 -> Element -> Element
- rot :: Float -> Element -> Element
- scale :: Float -> Element -> Element
- scaleV :: V2 -> Element -> Element
- transform :: M3 -> Element -> Element
- data Layer
- elements :: BackendIO => [Element] -> Layer
- view :: BackendIO => M3 -> [Element] -> Layer
- layer :: BackendIO => Object DefaultUniforms2D Geometry2 -> Layer
- layerPrg :: (BackendIO, Subset og pg) => Program pg Geometry2 -> Object og Geometry2 -> Layer
- program :: (Subset gs' gs, Subset gs'' gs, Subset os' os) => VertexShader gs' is os -> FragmentShader gs'' os' -> Program gs is
- subLayer :: Int -> Int -> Layer -> (Texture -> [Layer]) -> Layer
- data Object gs is
- object :: BackendIO => M3 -> [Element] -> Object DefaultUniforms2D Geometry2
- object1 :: BackendIO => Element -> Object `[Image, Depth, Transform2]` Geometry2
- (~~) :: (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 => M3 -> Object gs Geometry2 -> Object (View2 : gs) Geometry2
- type DefaultUniforms2D = Uniforms
- data Image
- data Depth
- data Transform2
- data View2
- data V3 = V3 !Float !Float !Float
- data M3 = M3 !V3 !V3 !V3
- mat3 :: (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> M3
- mul3 :: M3 -> M3 -> M3
- idMat3 :: M3
- transMat3 :: V2 -> M3
- rotMat3 :: Float -> M3
- scaleMat3 :: V2 -> M3
Elements
A rectangle with the aspect ratio adapted to its texture.
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
:: 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
module FWGL.Graphics.Color
textureFile :: String -> Texture Source
The same as textureURL
.
Creates a Texture
from a list of pixels.
Transformations
Two-dimensional vector.
Layers
Element layers
Object layers
layerPrg :: (BackendIO, Subset og pg) => Program pg Geometry2 -> Object og Geometry2 -> Layer Source
program :: (Subset gs' gs, Subset gs'' gs, Subset os' os) => VertexShader gs' is os -> FragmentShader gs'' os' -> Program gs is Source
Create a Program
from the shaders.
Sublayers
Custom 2D objects
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 (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.
An uniform that represents the texture used in the default 2D shader.
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.
An uniform that represents the view matrix used in the default 2D shader.
3D matrices
Three-dimensional vector.
3x3 matrix.
Eq M3 | |
Show M3 | |
GLES => UniformCPU M3 M3 | |
GLES => UniformCPU CM3 View2 | |
GLES => UniformCPU CM3 Transform2 |
mat3 :: (Float, Float, Float, Float, Float, Float, Float, Float, Float) -> M3 Source
Create a 3x3 matrix.