renderable-0.2.0.1: An API for managing renderable resources.

Safe HaskellSafe
LanguageHaskell2010

Data.Renderable

Synopsis

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

canAllocPrimitive :: r -> a -> Bool

Determines whether a renderer can be allocated for the primitive. A result of False will defer compilation until a later time (the next frame).

compilePrimitive :: r -> a -> m (Renderer m t)

Allocates resources for rendering the primitive and return a monadic call that renders the primitive using a transform. Tuples that with a call to clean up the allocated resources.

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.

type CleanOp m = m () Source

A CleanOp is an effectfull computaton that cleans up any resources allocated during the creation of an associated Rendering.

type Cache m t = IntMap (Renderer m t) Source

A cache of renderers.

data CacheStats a Source

A sum of lists of rendering hashes between two cache states. Used for debugging resource management.

Constructors

CacheStats 

Fields

cachedPrev :: [Int]

All the keys of the previous cache state.

cachedFound :: [Int]

The keys needed for the next state that were found in the previous cache (no need to allocate).

cachedMissing :: [Int]

The keys needed for the next state that were not found in the previous cache (these will need allocating).

cachedStale :: [Int]

The keys found in the previous cache that are not needed for the next state (these can be deallocated).

cachedNext :: [Int]

All the keys of the next cache state.

renderPrims :: (Functor m, 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 :: (Functor m, 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 :: (Functor m, 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.

appendRenderer :: Monad m => Renderer m t -> Renderer m t -> Renderer m t Source

Appends two renderers into one.