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

Safe HaskellSafe
LanguageHaskell2010

Data.Renderable

Synopsis

Documentation

class Primitive a where Source

A Primitive is the smallest thing can can be rendered in your graphics system. Some examples are points, lines, triangles and other shapes.

Associated Types

type PrimM a :: * -> * Source

The monad in which rendering calls will take place.

type PrimT a :: * Source

The type of the graphics transformation.

type PrimR a :: * Source

The datatype that holds cached resources such as references to windows, shaders, etc.

Methods

compilePrimitive :: Monad (PrimM a) => PrimR a -> a -> PrimM a (Rendering (PrimM a) (PrimT a)) Source

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

data Element m r t where Source

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

Constructors

Element :: (Monad m, Hashable a, Primitive a, m ~ PrimM a, r ~ PrimR a, t ~ PrimT 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

Hashable (Element m r t) Source 

Methods

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

hash :: Element m r t -> Int

Monoid t => Composite (Element m r t) m r t Source

Any Element is a composite of itself if its transform type is a monoid.

Methods

composite :: Element m r t -> [(t, Element m r t)] Source

class Composite a m r t where Source

A Composite is a type that can be broken down into a list of transformed primitives.

Methods

composite :: a -> [(t, Element m r t)] Source

Break down a Composite into a heterogeneous list of transformed primitives.

Instances

Composite a m r t => Composite [a] m r t Source

A list is a composite by compositing each element and concatenating the result.

Methods

composite :: [a] -> [(t, Element m r t)] Source

Composite a m r t => Composite (Maybe a) m r t Source

A Maybe is a composite if its contained type is composite. The result is is the composite of its contained type or an empty list.

Methods

composite :: Maybe a -> [(t, Element m r t)] Source

(Monoid t, Composite a m r t) => Composite (t, a) m r t Source

A tuple is a composite if its right type is a composite and the left type is the transform and the transform is a Monoid. In this case the result is the right type transformed by the left type.

Methods

composite :: (t, a) -> [(t, Element m r t)] Source

Monoid t => Composite (Element m r t) m r t Source

Any Element is a composite of itself if its transform type is a monoid.

Methods

composite :: Element m r t -> [(t, Element m r t)] Source

type Rendering m t = (m (), t -> m ()) 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.

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

A cache of renderings.

renderData :: (Composite a m r t, Hashable a, Monad m, Monoid t) => r -> Cache m t -> a -> m (Cache m t) Source

Render a datatype using renderings stored in the given cache, return a new cache that can be used to render the next datatype.