| License | BSD3 |
|---|---|
| Maintainer | ziocroc@gmail.com |
| Stability | experimental |
| Portability | GHC only |
| Safe Haskell | None |
| Language | Haskell2010 |
Graphics.Rendering.Ombra.Draw
Description
- module Graphics.Rendering.Ombra.OutBuffer
- data Draw o a
- data DrawState
- runDraw :: GLES => Int -> Int -> Ctx -> Draw GVec4 a -> IO a
- class (MonadGeometry (m o), MonadProgram (m o), MonadTexture (m o), MonadScreen (m o)) => MonadDraw o m where
- class MonadDrawBuffers m where
- class MonadDraw o m => MonadRead o m where
- class (GLES, Monad m) => MonadScreen m where
- clearColor :: (GLES, MonadGL m) => m ()
- clearDepth :: (GLES, MonadGL m) => m ()
- clearStencil :: (GLES, MonadGL m) => m ()
- data CullFace
- class (GLES, MonadGL m) => MonadCulling m where
- data ResStatus r
- preloadGeometry :: (GLES, GeometryVertex g) => Geometry g -> Draw o (Maybe String)
- preloadTexture :: GLES => Texture -> Draw o (Maybe String)
- removeGeometry :: (GLES, GeometryVertex g) => Geometry g -> Draw o ()
- removeTexture :: GLES => Texture -> Draw o ()
- checkGeometry :: (GLES, GeometryVertex g) => Geometry g -> Draw o (ResStatus ())
- checkTexture :: (GLES, Num a) => Texture -> Draw o (ResStatus (a, a))
Documentation
An implementation of MonadDraw and MonadDrawBuffers.
Instances
| GLES => MonadDrawBuffers Draw Source # | |
| GLES => MonadRead GVec4 Draw Source # | |
| (FragmentShaderOutput o, GLES) => MonadDraw o Draw Source # | |
| MonadBase IO (Draw o) Source # | |
| MonadBaseControl IO (Draw o) Source # | |
| Monad (Draw o) Source # | |
| Functor (Draw o) Source # | |
| Applicative (Draw o) Source # | |
| MonadIO (Draw o) Source # | |
| GLES => MonadCulling (Draw o) Source # | |
| GLES => MonadScreen (Draw o) Source # | |
| GLES => MonadTexture (Draw o) Source # | |
| type StM (Draw o) a Source # | |
Running the Draw monad
Draw actions
class (MonadGeometry (m o), MonadProgram (m o), MonadTexture (m o), MonadScreen (m o)) => MonadDraw o m where Source #
Monads that can be used to draw Images.
Minimal complete definition
Methods
withColorMask :: (Bool, Bool, Bool, Bool) -> m o a -> m o a Source #
withDepthTest :: Bool -> m o a -> m o a Source #
withDepthMask :: Bool -> m o a -> m o a Source #
class MonadDrawBuffers m where Source #
Monads that support drawing to GBuffers and DepthBuffers.
Minimal complete definition
Methods
drawBuffers :: Int -> Int -> Either (GBuffer t o) (GBufferInfo o) -> Either (DepthBuffer t') DepthBufferInfo -> m o a -> (forall t. GBuffer t o -> DepthBuffer t -> a -> m o' b) -> m o' b Source #
Draw an image to some buffers.
drawBuffers' :: Int -> Int -> Either (GBuffer t o) (GBufferInfo o) -> Either (DepthBuffer t1) DepthBufferInfo -> m o a -> m o' (a, GBuffer t2 o, DepthBuffer t3) Source #
Use this instead of drawBuffers if you need to reuse the newly
created buffers layer. They will be deleted from the GPU when the
'GBuffer'/'DepthBuffer' is garbage collected.
Instances
class MonadDraw o m => MonadRead o m where Source #
Minimal complete definition
readColor, readColorFloat, readDepth, readDepthFloat, readStencil
Methods
readColor :: (Int, Int, Int, Int) -> m o [Color] Source #
Read a rectangle of pixel colors from the screen (or texture).
readColorFloat :: (Int, Int, Int, Int) -> m o [Vec4] Source #
readColor variant that read color vectors.
readDepth :: (Int, Int, Int, Int) -> m o [Word16] Source #
Read a rectangle of pixel depths from the screen (or texture). Not supported on WebGL!
readDepthFloat :: (Int, Int, Int, Int) -> m o [Float] Source #
readDepth variants that read floats. Not supported on WebGL as well.
readStencil :: (Int, Int, Int, Int) -> m o [Word8] Source #
Read a rectangle of stencil values from the screen (or texture). Not supported on WebGL!
class (GLES, Monad m) => MonadScreen m where Source #
Minimal complete definition
currentViewport, resizeViewport
Instances
| GLES => MonadScreen (Draw o) Source # | |
clearColor :: (GLES, MonadGL m) => m () Source #
Clear the color buffer.
clearDepth :: (GLES, MonadGL m) => m () Source #
Clear the depth buffer.
clearStencil :: (GLES, MonadGL m) => m () Source #
Clear the stencil buffer.
Culling
class (GLES, MonadGL m) => MonadCulling m where Source #
Minimal complete definition
Methods
withCulling :: Maybe CullFace -> m a -> m a Source #
Instances
| GLES => MonadCulling (Draw o) Source # | |
Resources
In Ombra, GPU resources are allocated when they're needed, and they're kept alive by their corresponding CPU resources. Specifically, these resources are Geometries, Textures and Shaders. This means that, when a CPU resource is garbage collected, the GPU resource is also removed. The functions below let you manage allocation and deallocation manually. Note that if you try to use a resource that was deallocated with the remove* functions, it will be allocated again.
preloadGeometry :: (GLES, GeometryVertex g) => Geometry g -> Draw o (Maybe String) Source #
Manually allocate a Geometry in the GPU. Eventually returns an error
string.
preloadTexture :: GLES => Texture -> Draw o (Maybe String) Source #
Manually allocate a Texture in the GPU.
removeGeometry :: (GLES, GeometryVertex g) => Geometry g -> Draw o () Source #
Manually delete a Geometry from the GPU.
checkGeometry :: (GLES, GeometryVertex g) => Geometry g -> Draw o (ResStatus ()) Source #
Check if a Geometry failed to load.