Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Draw a
- data DrawState
- refDrawCtx :: GLES => Ctx -> Draw a -> IORef DrawState -> IO a
- runDrawCtx :: Ctx -> Draw a -> DrawState -> IO (a, DrawState)
- execDrawCtx :: Ctx -> Draw a -> DrawState -> IO DrawState
- evalDrawCtx :: Ctx -> Draw a -> DrawState -> IO a
- drawState :: GLES => Int -> Int -> IO DrawState
- class MonadIO m => MonadGL m where
- class GLES => MonadScreen m where
- type MonadObject m = (MonadProgram m, MonadTexture m, MonadScreen m, MonadGeometry m, MonadDrawingMode m)
- drawInit :: GLES => Draw ()
- clearBuffers :: (GLES, MonadGL m) => [Buffer] -> m ()
- drawLayer :: MonadObject m => Layer' Drawable t a -> m a
- data ResStatus r
- preloadGeometry :: GLES => Geometry (i ': is) -> Draw (Maybe String)
- preloadTexture :: GLES => Texture -> Draw (Maybe String)
- preloadProgram :: GLES => Program gs is -> Draw (Maybe String)
- removeGeometry :: GLES => Geometry (i ': is) -> Draw ()
- removeTexture :: GLES => Texture -> Draw ()
- removeProgram :: GLES => Program gs is -> Draw ()
- checkGeometry :: GLES => Geometry (i ': is) -> Draw (ResStatus ())
- checkTexture :: (GLES, Num a) => Texture -> Draw (ResStatus (a, a))
- checkProgram :: GLES => Program gs is -> Draw (ResStatus ())
- hasVertexArrayObjects :: GLES => Ctx -> IO Bool
- hasFloatTextures :: GLES => Ctx -> IO Bool
- hasDrawBuffers :: GLES => Ctx -> IO Bool
- hasStandardDerivatives :: GLES => Ctx -> IO Bool
Documentation
A state monad on top of GL
.
Running the Draw monad
refDrawCtx :: GLES => Ctx -> Draw a -> IORef DrawState -> IO a Source #
Run a Draw action using an IORef and a context.
Create a DrawState
.
Draw actions
class GLES => MonadScreen m where Source #
currentViewport, resizeViewport
resizeViewport :: Int -> Int -> m () Source #
GLES => MonadScreen Draw Source # | |
type MonadObject m = (MonadProgram m, MonadTexture m, MonadScreen m, MonadGeometry m, MonadDrawingMode m) 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 Programs. 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 => Geometry (i ': is) -> Draw (Maybe String) Source #
Manually allocate a Geometry
in the GPU. Eventually returns an error
string.
preloadTexture :: GLES => Texture -> Draw (Maybe String) Source #
Manually allocate a Texture
in the GPU.
preloadProgram :: GLES => Program gs is -> Draw (Maybe String) Source #
Manually allocate a Program
in the GPU.
removeGeometry :: GLES => Geometry (i ': is) -> Draw () Source #
Manually delete a Geometry
from the GPU.
checkGeometry :: GLES => Geometry (i ': is) -> Draw (ResStatus ()) Source #
Check if a Geometry
failed to load.
checkTexture :: (GLES, Num a) => Texture -> Draw (ResStatus (a, a)) Source #
Check if a Texture
failed to load. Eventually returns the texture width
and height.
checkProgram :: GLES => Program gs is -> Draw (ResStatus ()) Source #
Check if a Program
failed to load.
Extensions
hasVertexArrayObjects :: GLES => Ctx -> IO Bool Source #
This extension is fundamental and Ombra won't work without it.
hasFloatTextures :: GLES => Ctx -> IO Bool Source #
Required for the buffers* layer functions. May not be supported on older hardware.