renderable-0.0.0.2: Provides a nice API for rendering data types that change over time.

Safe HaskellSafe
LanguageHaskell2010

Data.Renderable

Synopsis

Documentation

renderData :: (Monad m, Renderable a, Monoid (RenderTfrm a)) => Cache m (RenderTfrm a) -> a -> m () Source

Render a datatype using renderings stored in the given cache.

renderDataHidden :: (Renderable a, Monad m, Monoid (RenderTfrm a)) => Cache m (RenderTfrm a) -> RenderTfrm a -> a -> m () Source

Render only the hidden layers of a datatype using renderings stored in the given cache. This is sometimes useful for debugging.

renderComposite :: (Monad m, Monoid t) => Cache m t -> t -> Composite t -> m () Source

Render the composite of a datatype using renderings stored in the given cache.

attachIfNeeded :: (Renderable a, Monad (RenderMonad a), Monoid (RenderTfrm a), Hashable a) => RenderRsrc a -> Cache (RenderMonad a) (RenderTfrm a) -> a -> RenderMonad a (Cache (RenderMonad a) (RenderTfrm a)) Source

If needed, create a new rendering given some resources, insert it in the cache and return the new cache.

detachUnused :: (Monad m, Renderable a) => Cache m t -> a -> m (Cache m t) Source

Detach any renderings that are not needed to render the given data.

detach :: Monad m => Cache m t -> Int -> m (Cache m t) Source

Remove a rendering from a cache and clean up the resources allocated for that rendering.

class Decomposable a m r t where Source

An instance of Decomposable can be broken down into a number of elements.

Methods

decompose :: a -> [Element m r t] Source

Instances

Decomposable (Element m r t) m r t Source

Any element is decomposable by returning a list consisting of itself.

Methods

decompose :: Element m r t -> [Element m r t] Source

data Element m r t where Source

Element is a generic existential type that can be used to enclose instances of Renderable in order to contain them all in a heterogeneous list. m, r and t must be shared with all Renderable instances stored in a heterogeneous list of Elements.

Constructors

Element :: (Monad m, Show a, Hashable a, Renderable a, m ~ RenderMonad a, r ~ RenderRsrc a, t ~ RenderTfrm a) => a -> Element m r t 

Instances

Eq (Element m r t) Source 

Methods

(==) :: Element m r t -> Element m r t -> Bool

(/=) :: Element m r t -> Element m r t -> Bool

Show (Element m r t) Source 

Methods

showsPrec :: Int -> Element m r t -> ShowS

show :: Element m r t -> String

showList :: [Element m r t] -> ShowS

Hashable (Element m r t) Source 

Methods

hashWithSalt :: Int -> Element m r t -> Int

hash :: Element m r t -> Int

Renderable (Element m r t) Source

Any Element is renderable by rendering its contained datatype.

Associated Types

type RenderMonad (Element m r t) :: * -> * Source

type RenderTfrm (Element m r t) :: * Source

type RenderRsrc (Element m r t) :: * Source

Methods

nameOf :: Element m r t -> String Source

cache :: RenderRsrc (Element m r t) -> Cache (RenderMonad (Element m r t)) (RenderTfrm (Element m r t)) -> Element m r t -> RenderMonad (Element m r t) (Cache (RenderMonad (Element m r t)) (RenderTfrm (Element m r t))) Source

composite :: Element m r t -> Composite (RenderTfrm (Element m r t)) Source

Decomposable (Element m r t) m r t Source

Any element is decomposable by returning a list consisting of itself.

Methods

decompose :: Element m r t -> [Element m r t] Source

type RenderMonad (Element m r t) = m Source 
type RenderTfrm (Element m r t) = t Source 
type RenderRsrc (Element m r t) = r Source 

class Renderable a where Source

Associated Types

type RenderMonad a :: * -> * Source

The monad needed to render the datatype. In most cases this is probably IO.

type RenderTfrm a :: * Source

The datatype that is used to transform renderings.

type RenderRsrc a :: * Source

The datatype that holds cached resources that will be used to composite and render the datatype.

Methods

nameOf :: a -> String Source

The name of a renderable datatype. This is mostly for debugging.

cache :: (Monad (RenderMonad a), Monoid (RenderTfrm a)) => RenderRsrc a -> Cache (RenderMonad a) (RenderTfrm a) -> a -> RenderMonad a (Cache (RenderMonad a) (RenderTfrm a)) Source

Store the rendering of a datatype in a cache keyed by the hash of that datatype. Returns the new cache.

composite :: a -> Composite (RenderTfrm a) Source

The entire composite list of renderings for a given datatype.

Instances

(Renderable a, Hashable a) => Renderable [a] Source

A list of renderable instances is renderable by rendering each instance.

Associated Types

type RenderMonad [a] :: * -> * Source

type RenderTfrm [a] :: * Source

type RenderRsrc [a] :: * Source

Methods

nameOf :: [a] -> String Source

cache :: RenderRsrc [a] -> Cache (RenderMonad [a]) (RenderTfrm [a]) -> [a] -> RenderMonad [a] (Cache (RenderMonad [a]) (RenderTfrm [a])) Source

composite :: [a] -> Composite (RenderTfrm [a]) Source

(Renderable a, Hashable a, Show a) => Renderable (Maybe a) Source

A Maybe is renderable by rendering the datatype contained in the Just constructor or by rendering nothing.

Associated Types

type RenderMonad (Maybe a) :: * -> * Source

type RenderTfrm (Maybe a) :: * Source

type RenderRsrc (Maybe a) :: * Source

((~) * t (RenderTfrm a), Show t, Monoid t, Hashable a, Renderable a) => Renderable (t, a) Source

A tuple is renderable when it is a pairing of a transform and another renderable datatype.

Associated Types

type RenderMonad (t, a) :: * -> * Source

type RenderTfrm (t, a) :: * Source

type RenderRsrc (t, a) :: * Source

Methods

nameOf :: (t, a) -> String Source

cache :: RenderRsrc (t, a) -> Cache (RenderMonad (t, a)) (RenderTfrm (t, a)) -> (t, a) -> RenderMonad (t, a) (Cache (RenderMonad (t, a)) (RenderTfrm (t, a))) Source

composite :: (t, a) -> Composite (RenderTfrm (t, a)) Source

Renderable (Element m r t) Source

Any Element is renderable by rendering its contained datatype.

Associated Types

type RenderMonad (Element m r t) :: * -> * Source

type RenderTfrm (Element m r t) :: * Source

type RenderRsrc (Element m r t) :: * Source

Methods

nameOf :: Element m r t -> String Source

cache :: RenderRsrc (Element m r t) -> Cache (RenderMonad (Element m r t)) (RenderTfrm (Element m r t)) -> Element m r t -> RenderMonad (Element m r t) (Cache (RenderMonad (Element m r t)) (RenderTfrm (Element m r t))) Source

composite :: Element m r t -> Composite (RenderTfrm (Element m r t)) Source

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

A cache of renderings.

data Rendering m t Source

A rendering is a type that contains some effectful computation for displaying something given a transform. It also contains an effectful computation for cleaning up any resources allocated during its creation.

Constructors

Rendering 

Fields

Instances

Monad m => Monoid (Rendering m t) Source 

Methods

mempty :: Rendering m t

mappend :: Rendering m t -> Rendering m t -> Rendering m t

mconcat :: [Rendering m t] -> Rendering m t

type Composite a = [(Int, Maybe a)] Source

A composite is a representation of the entire rendered datatype. It is a flattened list of all the renderings (denoted by hash), along with that rendering's local transformation. If a rendering is explicitly run by another rendering (as in a Renderable class definition) then the transformation for that rendering should be Nothing, which will keep renderComposite from running that rendering in addition to the rendering its included in. For example: [(0, Just $ Transform (10,10) (0.5,0.5) 0) ,(1, Nothing) ] The above is a composite of two renderings, the first will be rendered by renderComposite using the given transform while the second is effectively hidden but present. Being present in the composite will keep detachUnused from detaching and cleaning the rendering.