ombra-0.3.1.0: Render engine.

Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Ombra.Layer

Contents

Synopsis

Documentation

type Layer = Layer' Drawable () () Source #

An Object associated with a program.

layer :: (Subset progAttr grpAttr, Subset progUni grpUni) => Program progUni progAttr -> Object grpUni grpAttr -> Layer' s t () Source #

Create a simple Layer from a Program and an Object.

over :: Layer -> Layer -> Layer infixl 1 Source #

Draw the first Layer over the second one. This means that the first Layer will use the same buffers (color, depth, stencil) of the second, but the visibility of the objects still depends on their depth.

clear :: [Buffer] -> Layer' s t () Source #

Layer that clear some buffers. For instance, clear [ColorBuffer] fills the screen with a black rectangle, without affecting the depth buffer.

Programs

type Compatible pgs vgs fgs = EqualOrErr pgs (Union vgs fgs) ((((Text "Incompatible shader uniforms" :$$: (Text " Vertex shader uniforms: " :<>: ShowType vgs)) :$$: (Text " Fragment shader uniforms: " :<>: ShowType fgs)) :$$: (Text " United shader uniforms: " :<>: ShowType (Union vgs fgs))) :$$: (Text " Program uniforms: " :<>: ShowType pgs)) Source #

Compatible shaders.

data Program gs is Source #

A vertex shader associated with a compatible fragment shader.

Instances

Eq (Program gs is) Source # 

Methods

(==) :: Program gs is -> Program gs is -> Bool #

(/=) :: Program gs is -> Program gs is -> Bool #

Hashable (Program gs is) Source # 

Methods

hashWithSalt :: Int -> Program gs is -> Int #

hash :: Program gs is -> Int #

program :: (ShaderVars vgs, ShaderVars vis, VOShaderVars os, ShaderVars fgs, Compatible pgs vgs fgs) => VertexShader vgs vis os -> FragmentShader fgs os -> Program pgs vis Source #

Create a Program from the shaders.

Sublayers

subLayer :: Int -> Int -> Layer -> (Texture -> Layer) -> Layer Source #

Alias for colorSubLayer.

colorSubLayer Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a Texture.

-> (Texture -> Layer)

Layers using the texture.

-> Layer 

Use a Layer as a Texture on another.

depthSubLayer Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a depth Texture.

-> (Texture -> Layer)

Layers using the texture.

-> Layer 

Use a Layer as a depth Texture on another.

colorDepthSubLayer Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on the Textures.

-> (Texture -> Texture -> Layer)

Color, depth.

-> Layer 

Combination of colorSubLayer and depthSubLayer.

colorStencilSubLayer Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer

Layer to draw on a Texture

-> (Texture -> Layer)

Color.

-> Layer 

colorSubLayer with a stencil buffer.

colorSubLayer' Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

First pixel to read X

-> Int

First pixel to read Y

-> Int

Width of the rectangle to read

-> Int

Height of the rectangle to read

-> Layer

Layer to draw on a Texture.

-> (Texture -> [Color] -> Layer)

Function using the texture.

-> Layer 

Extended version of colorSubLayer that reads and converts the Texture pixels.

depthSubLayer' Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

First pixel to read X

-> Int

First pixel to read Y

-> Int

Width of the rectangle to read

-> Int

Height of the rectangle to read

-> Layer

Layer to draw on a depth Texture.

-> (Texture -> [Word8] -> Layer)

Layers using the texture.

-> Layer 

Extended version of depthSubLayer. Not supported on WebGL.

colorDepthSubLayer' Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

First pixel to read X

-> Int

First pixel to read Y

-> Int

Width of the rectangle to read

-> Int

Height of the rectangle to read

-> Layer

Layer to draw on a Texture

-> (Texture -> Texture -> [Color] -> [Word8] -> Layer)

Layers using the texture.

-> Layer 

Extended version of colorDepthSubLayer. Not supported on WebGL.

colorStencilSubLayer' Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

First pixel to read X

-> Int

First pixel to read Y

-> Int

Width of the rectangle to read

-> Int

Height of the rectangle to read

-> Layer

Layer to draw on a Texture.

-> (Texture -> [Color] -> Layer)

Function using the texture.

-> Layer 

colorSubLayer' with an additional stencil buffer.

buffersSubLayer Source #

Arguments

:: Int

Textures width.

-> Int

Textures height.

-> Int

Number of colors.

-> Layer

Layer to draw.

-> ([Texture] -> Layer)

Function using the textures.

-> Layer 

Draw a Layer with multiple floating point colors (use Fragment2, Fragment3, etc.) to some Textures and use them to create another Layer.

buffersDepthSubLayer Source #

Arguments

:: Int

Textures width.

-> Int

Textures height.

-> Int

Number of colors.

-> Layer

Layer to draw.

-> ([Texture] -> Texture -> Layer)

Function using the buffers textures and the depth texture.

-> Layer 

Combination of buffersSubLayer and depthSubLayer.

buffersStencilSubLayer Source #

Arguments

:: Int

Textures width.

-> Int

Textures height.

-> Int

Number of colors.

-> Layer

Layer to draw.

-> ([Texture] -> Layer)

Function using the texture.

-> Layer 

buffersSubLayer with an additional stencil buffer.

Layers with return values

Functions like subLayer create temporary textures that usually have to be freed immediately after drawing the layer, otherwise they may waste a lot of GPU memory if subLayer is called in every frame. The Layer' type lets you extract those textures after having made permanent.

data Layer' s t a Source #

A layer with a return value. It may also be NonDrawable, this means that there are some protected temporary resources and you have to call drawable to turn it into a normal layer. The second parameter prevents the TTextures from being returned by a NonDrawable layer in a drawable operation.

Note that layers are monads: flip (>>) is equivalent to over for Drawable layers, while (>>=), in combination with the *ToTexture functions, can be used to achieve the same effect of the subLayer functions.

Instances

Monad (Layer' s t) Source # 

Methods

(>>=) :: Layer' s t a -> (a -> Layer' s t b) -> Layer' s t b #

(>>) :: Layer' s t a -> Layer' s t b -> Layer' s t b #

return :: a -> Layer' s t a #

fail :: String -> Layer' s t a #

Functor (Layer' s t) Source # 

Methods

fmap :: (a -> b) -> Layer' s t a -> Layer' s t b #

(<$) :: a -> Layer' s t b -> Layer' s t a #

Applicative (Layer' s t) Source # 

Methods

pure :: a -> Layer' s t a #

(<*>) :: Layer' s t (a -> b) -> Layer' s t a -> Layer' s t b #

(*>) :: Layer' s t a -> Layer' s t b -> Layer' s t b #

(<*) :: Layer' s t a -> Layer' s t b -> Layer' s t a #

drawable :: (forall t. Layer' NonDrawable t a) -> Layer' s t a Source #

Free the temporary resources associated with a NonDrawable layer, before drawing it.

castLayer :: Layer -> Layer' Drawable t () Source #

Make the type of a simple Layer more generic.

Temporary textures

data TTexture t Source #

Temporary texture.

Instances

GLES => Eq (TTexture t) Source # 

Methods

(==) :: TTexture t -> TTexture t -> Bool #

(/=) :: TTexture t -> TTexture t -> Bool #

withTTexture :: TTexture t -> (Texture -> Layer) -> Layer' NonDrawable t () Source #

Draw a Layer using a temporary texture.

permanent :: TTexture t -> Layer' NonDrawable t Texture Source #

Make a TTexture permanent. Its lifetime is still bound to the Texture returned.

Drawing to textures

depthToTexture Source #

Arguments

:: Int

Textures width.

-> Int

Textures height.

-> Layer' s t a

Layer to draw.

-> Layer' NonDrawable t (a, TTexture t) 

Draw a Layer to a depth Texture.

colorDepthToTexture Source #

Arguments

:: Int

Textures width.

-> Int

Textures height.

-> Layer' s t a

Layer to draw.

-> Layer' NonDrawable t (a, TTexture t, TTexture t) 

Draw a Layer to a color Texture and a depth Texture.

colorStencilToTexture Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Layer' s t a 
-> Layer' NonDrawable t (a, TTexture t) 

Draw a Layer to a color Texture with an additional stencil buffer.

colorToTexture' Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

First pixel to read X.

-> Int

First pixel to read Y.

-> Int

Width of the rectangle to read.

-> Int

Height of the rectangle to read.

-> Layer' s t a

Layer to draw.

-> Layer' NonDrawable t (a, TTexture t, [Color]) 

Draw a Layer to a Texture, reading the content of the texture.

depthToTexture' Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

First pixel to read X.

-> Int

First pixel to read Y.

-> Int

Width of the rectangle to read.

-> Int

Height of the rectangle to read.

-> Layer' s t a

Layer to draw.

-> Layer' NonDrawable t (a, TTexture t, [Word8]) 

Draw a Layer to a depth Texture, reading the content of the texture. Not supported on WebGL.

colorDepthToTexture' Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

First pixel to read X.

-> Int

First pixel to read Y.

-> Int

Width of the rectangle to read.

-> Int

Height of the rectangle to read.

-> Layer' s t a

Layer to draw.

-> Layer' NonDrawable t (a, TTexture t, TTexture t, [Color], [Word8]) 

Combination of colorToTexture' and depthToTexture'. Not supported on WebGL.

colorStencilToTexture' Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

First pixel to read X.

-> Int

First pixel to read Y.

-> Int

Width of the rectangle to read.

-> Int

Height of the rectangle to read.

-> Layer' s t a

Layer to draw.

-> Layer' NonDrawable t (a, TTexture t, [Color]) 

colorToTexture' with an additional stencil buffer.

buffersDepthToTexture Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

Number of colors.

-> Layer' s t a

Layer to draw.

-> Layer' NonDrawable t (a, [TTexture t], TTexture t) 

Draw a Layer with multiple floating point colors (use Fragment2, Fragment3, etc.) to some Textures and to a depth Texture.

buffersStencilToTexture Source #

Arguments

:: Int

Texture width.

-> Int

Texture height.

-> Int

Number of colors.

-> Layer' s t a

Layer to draw.

-> Layer' NonDrawable t (a, [TTexture t]) 

Draw a Layer with multiple floating point colors (use Fragment2, Fragment3, etc.) to some Textures with an additional stencil buffer.