| Safe Haskell | Safe |
|---|---|
| Language | Haskell2010 |
Data.Renderable
- data RenderStrategy m t r a = RenderStrategy {
- canAllocPrimitive :: r -> a -> Bool
- compilePrimitive :: r -> a -> m (Renderer m t)
- type Renderer m t = (CleanOp m, Rendering m t)
- type Rendering m t = t -> m ()
- type CleanOp m = m ()
- type Cache m t = IntMap (Renderer m t)
- data CacheStats a = CacheStats {
- cachedPrev :: [Int]
- cachedFound :: [Int]
- cachedMissing :: [Int]
- cachedStale :: [Int]
- cachedNext :: [Int]
- renderPrims :: (Monad m, Monoid t, Hashable a) => RenderStrategy m t r a -> r -> Cache m t -> [(t, a)] -> m (Cache m t)
- renderPrimsDebug :: (MonadIO m, Monoid t, Hashable a) => Bool -> RenderStrategy m t r a -> r -> Cache m t -> [(t, a)] -> m (Cache m t)
- renderPrimsWithStats :: (Monad m, Monoid t, Hashable a) => RenderStrategy m t r a -> r -> Cache m t -> [(t, a)] -> m (Cache m t, CacheStats a)
- emptyRenderer :: Monad m => Renderer m t
- appendRenderer :: Monad m => Renderer m t -> Renderer m t -> Renderer m t
Documentation
data RenderStrategy m t r a Source
A RenderStrategy is a method for creating a renderer that can render
your primitives. Examples of primitives are are points, lines, triangles and
other shapes. A RenderStrategy is parameterized by four types -
m - the monad in which rendering calls will take place.
t - type of the graphics transformation that can be applied to the
renderer
r - type that holds static resources such as windows, shaders, etc.
a - type of the primitive that can be renderered.
Constructors
| RenderStrategy | |
Fields
| |
type Renderer m t = (CleanOp m, Rendering m t) Source
A Renderer is the pairing of a Rendering and a Cleanup.
type Rendering m t = t -> m () Source
A Rendering is an effectful computation for displaying something given a transform.
A CleanOp is an effectfull computaton that cleans up any resources allocated during the creation of an associated Rendering.
data CacheStats a Source
A sum of lists of rendering hashes between two cache states. Used for debugging resource management.
Constructors
| CacheStats | |
Fields
| |
renderPrims :: (Monad m, Monoid t, Hashable a) => RenderStrategy m t r a -> r -> Cache m t -> [(t, a)] -> m (Cache m t) Source
Render a list of primitives using renderings stored in the given cache, return a new cache that can be used to render the next list of primitives.
renderPrimsDebug :: (MonadIO m, Monoid t, Hashable a) => Bool -> RenderStrategy m t r a -> r -> Cache m t -> [(t, a)] -> m (Cache m t) Source
Render a list of primitives using renderings stored in the given cache, return a new cache that can be used to render the next list of primitives. Optionally print some debug info.
renderPrimsWithStats :: (Monad m, Monoid t, Hashable a) => RenderStrategy m t r a -> r -> Cache m t -> [(t, a)] -> m (Cache m t, CacheStats a) Source
Render a list of primitives using renderings stored in the given cache, return a new cache that can be used to render the next list of primitives, along with some info about the comparison of the given and returned cache.
emptyRenderer :: Monad m => Renderer m t Source
Create a renderer that renders nothing and releases no resources.