Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Buffer
- type Layer = Layer' Drawable () ()
- layer :: (Subset progAttr grpAttr, Subset progUni grpUni) => Program progUni progAttr -> Object grpUni grpAttr -> Layer' s t ()
- over :: Layer -> Layer -> Layer
- clear :: [Buffer] -> Layer' s t ()
- 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))
- data Program gs is
- program :: (ShaderVars vgs, ShaderVars vis, VOShaderVars os, ShaderVars fgs, Compatible pgs vgs fgs) => VertexShader vgs vis os -> FragmentShader fgs os -> Program pgs vis
- subLayer :: Int -> Int -> Layer -> (Texture -> Layer) -> Layer
- colorSubLayer :: Int -> Int -> Layer -> (Texture -> Layer) -> Layer
- depthSubLayer :: Int -> Int -> Layer -> (Texture -> Layer) -> Layer
- colorDepthSubLayer :: Int -> Int -> Layer -> (Texture -> Texture -> Layer) -> Layer
- colorStencilSubLayer :: Int -> Int -> Layer -> (Texture -> Layer) -> Layer
- colorSubLayer' :: Int -> Int -> Int -> Int -> Int -> Int -> Layer -> (Texture -> [Color] -> Layer) -> Layer
- depthSubLayer' :: Int -> Int -> Int -> Int -> Int -> Int -> Layer -> (Texture -> [Word8] -> Layer) -> Layer
- colorDepthSubLayer' :: Int -> Int -> Int -> Int -> Int -> Int -> Layer -> (Texture -> Texture -> [Color] -> [Word8] -> Layer) -> Layer
- colorStencilSubLayer' :: Int -> Int -> Int -> Int -> Int -> Int -> Layer -> (Texture -> [Color] -> Layer) -> Layer
- buffersSubLayer :: Int -> Int -> Int -> Layer -> ([Texture] -> Layer) -> Layer
- buffersDepthSubLayer :: Int -> Int -> Int -> Layer -> ([Texture] -> Texture -> Layer) -> Layer
- buffersStencilSubLayer :: Int -> Int -> Int -> Layer -> ([Texture] -> Layer) -> Layer
- data Layer' s t a
- data LayerStatus
- drawable :: (forall t. Layer' NonDrawable t a) -> Layer' s t a
- castLayer :: Layer -> Layer' Drawable t ()
- data TTexture t
- withTTexture :: TTexture t -> (Texture -> Layer) -> Layer' NonDrawable t ()
- permanent :: TTexture t -> Layer' NonDrawable t Texture
- depthToTexture :: Int -> Int -> Layer' s t a -> Layer' NonDrawable t (a, TTexture t)
- colorDepthToTexture :: Int -> Int -> Layer' s t a -> Layer' NonDrawable t (a, TTexture t, TTexture t)
- colorStencilToTexture :: Int -> Int -> Layer' s t a -> Layer' NonDrawable t (a, TTexture t)
- colorToTexture' :: Int -> Int -> Int -> Int -> Int -> Int -> Layer' s t a -> Layer' NonDrawable t (a, TTexture t, [Color])
- depthToTexture' :: Int -> Int -> Int -> Int -> Int -> Int -> Layer' s t a -> Layer' NonDrawable t (a, TTexture t, [Word8])
- colorDepthToTexture' :: Int -> Int -> Int -> Int -> Int -> Int -> Layer' s t a -> Layer' NonDrawable t (a, TTexture t, TTexture t, [Color], [Word8])
- colorStencilToTexture' :: Int -> Int -> Int -> Int -> Int -> Int -> Layer' s t a -> Layer' NonDrawable t (a, TTexture t, [Color])
- buffersDepthToTexture :: Int -> Int -> Int -> Layer' s t a -> Layer' NonDrawable t (a, [TTexture t], TTexture t)
- buffersStencilToTexture :: Int -> Int -> Int -> Layer' s t a -> Layer' NonDrawable t (a, [TTexture t])
Documentation
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 [
fills
the screen with a black rectangle, without affecting the depth buffer.ColorBuffer
]
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.
A vertex shader associated with a compatible fragment shader.
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
:: Int | Texture width. |
-> Int | Texture height. |
-> Layer | Layer to draw on the
|
-> (Texture -> Texture -> Layer) | Color, depth. |
-> Layer |
Combination of colorSubLayer
and depthSubLayer
.
:: Int | Texture width. |
-> Int | Texture height. |
-> Layer | Layer to draw on a |
-> (Texture -> Layer) | Color. |
-> Layer |
colorSubLayer
with a stencil buffer.
:: 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 -> [Color] -> Layer) | Function using the texture. |
-> Layer |
Extended version of colorSubLayer
that reads and converts the Texture
pixels.
:: 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 -> [Word8] -> Layer) | Layers using the texture. |
-> Layer |
Extended version of depthSubLayer
. Not supported on WebGL.
:: 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] -> [Word8] -> Layer) | Layers using the texture. |
-> Layer |
Extended version of colorDepthSubLayer
. Not supported on WebGL.
colorStencilSubLayer' Source #
:: 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 -> [Color] -> Layer) | Function using the texture. |
-> Layer |
colorSubLayer'
with an additional stencil buffer.
:: 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 #
:: 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.
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 TTexture
s
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.
drawable :: (forall t. Layer' NonDrawable t a) -> Layer' s t a Source #
Free the temporary resources associated with a NonDrawable layer, before drawing it.
Temporary textures
withTTexture :: TTexture t -> (Texture -> Layer) -> Layer' NonDrawable t () Source #
Draw a Layer using a temporary texture.
Drawing to textures
:: 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 #
:: 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.