ombra-0.3.0.0: Render engine.

Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.D2

Contents

Description

Simplified 2D graphics system.

Synopsis

2D Objects

type Object2D = Object Uniforms2D Geometry2D Source #

A simple 2D Object, without the View2 matrix.

type IsObject2D gs is = (Subset Geometry2D is, Subset (View2 ': Uniforms2D) gs, ShaderVars is, ShaderVars gs) Source #

2D objects compatible with the standard 2D shader program.

rect :: GLES => Texture -> Object2D Source #

A rectangle with a specified Texture.

image :: GLES => Texture -> Object2D Source #

A rectangle with the aspect ratio adapted to its texture.

sprite :: GLES => Texture -> Object2D Source #

A rectangle with the size and aspect ratio adapted to the screen, assuming that you're using viewScreen or screenMat3.

depth :: (MemberGlobal Depth gs, GLES) => Float -> Object gs is -> Object gs is Source #

Set the depth of a 2D Object.

poly :: GLES => Texture -> Geometry is -> Object Uniforms2D is Source #

A 2D object with a specified Geometry.

Transformations

trans :: (MemberGlobal Transform2 gs, GLES) => Vec2 -> Object gs is -> Object gs is Source #

Translate a 2D Object.

rot :: (MemberGlobal Transform2 gs, GLES) => Float -> Object gs is -> Object gs is Source #

Rotate a 2D Object.

scale :: (MemberGlobal Transform2 gs, GLES) => Float -> Object gs is -> Object gs is Source #

Scale a 2D Object.

scaleV :: (MemberGlobal Transform2 gs, GLES) => Vec2 -> Object gs is -> Object gs is Source #

Scale a 2D Object in two dimensions.

scaleTex :: (MemberGlobal Transform2 gs, GLES) => Texture -> Object gs is -> Object gs is Source #

Scale an Object so that it has the same size as the Texture, assuming viewScreen or screenMat3.

scaleTexAR :: (MemberGlobal Transform2 gs, GLES) => Texture -> Object gs is -> Object gs is Source #

Scale an Object so that it has the same aspect ratio as the Texture

scaleV $ Vec2 1 (texture height / texture width).

transform :: (MemberGlobal Transform2 gs, GLES) => Mat3 -> Object gs is -> Object gs is Source #

Transform a 2D Object.

Layers

view :: (ShaderVars gs, ShaderVars is, GLES) => Mat3 -> [Object gs is] -> Object (View2 ': gs) is Source #

Create a group of objects with a view matrix.

viewScreen :: (ShaderVars gs, ShaderVars is, GLES) => Mat3 -> [Object gs is] -> Object (View2 ': gs) is Source #

Create a group of objects with a view matrix and screenMat3.

viewVP :: (ShaderVars gs, ShaderVars is, GLES) => (Vec2 -> Mat3) -> [Object gs is] -> Object (View2 ': gs) is Source #

Create a group of objects with a view matrix, depending on the size of the framebuffer.

layerS :: IsObject2D gs is => Object gs is -> Layer' s t () Source #

A Layer with the standard 2D program.

Transformation matrices

transMat3 :: Vec2 -> Mat3 Source #

3x3 translation matrix.

rotMat3 :: Float -> Mat3 Source #

3x3 rotation matrix.

scaleMat3 :: Vec2 -> Mat3 Source #

3x3 scale matrix.

screenMat3 Source #

Arguments

:: Vec2

Viewport size.

-> Mat3 

Convert the screen coordinates to GL coordinates.

Uniforms

data Image Source #

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

Constructors

Image GSampler2D 

Instances

Generic Image Source # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

type Rep Image Source # 
type Rep Image = D1 (MetaData "Image" "Graphics.Rendering.Ombra.Shader.Default2D" "ombra-0.3.0.0-AelVPs5t89yJbS9QoxoRjc" False) (C1 (MetaCons "Image" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GSampler2D)))

data Depth Source #

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

Constructors

Depth GFloat 

Instances

Generic Depth Source # 

Associated Types

type Rep Depth :: * -> * #

Methods

from :: Depth -> Rep Depth x #

to :: Rep Depth x -> Depth #

type Rep Depth Source # 
type Rep Depth = D1 (MetaData "Depth" "Graphics.Rendering.Ombra.Shader.Default2D" "ombra-0.3.0.0-AelVPs5t89yJbS9QoxoRjc" False) (C1 (MetaCons "Depth" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GFloat)))

data Transform2 Source #

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

Constructors

Transform2 GMat3 

Instances

Generic Transform2 Source # 

Associated Types

type Rep Transform2 :: * -> * #

type Rep Transform2 Source # 
type Rep Transform2 = D1 (MetaData "Transform2" "Graphics.Rendering.Ombra.Shader.Default2D" "ombra-0.3.0.0-AelVPs5t89yJbS9QoxoRjc" False) (C1 (MetaCons "Transform2" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GMat3)))

data View2 Source #

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

Constructors

View2 GMat3 

Instances

Generic View2 Source # 

Associated Types

type Rep View2 :: * -> * #

Methods

from :: View2 -> Rep View2 x #

to :: Rep View2 x -> View2 #

type Rep View2 Source # 
type Rep View2 = D1 (MetaData "View2" "Graphics.Rendering.Ombra.Shader.Default2D" "ombra-0.3.0.0-AelVPs5t89yJbS9QoxoRjc" False) (C1 (MetaCons "View2" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 GMat3)))