wumpus-basic-0.9.0: Common drawing utilities built on wumpus-core.

PortabilityGHC
Stabilityunstable
Maintainerstephen.tetley@gmail.com

Wumpus.Basic.Graphic.Drawing

Description

Drawing with trace - a Writer like monad collecting intermediate graphics - and drawing context - a reader monad of attributes - font_face, fill_colour etc.

Synopsis

Documentation

data DrawingT u m a Source

Instances

Monad m => Monad (DrawingT u m) 
Monad m => Functor (DrawingT u m) 
Monad m => Applicative (DrawingT u m) 
Monad m => DrawingCtxM (DrawingT u m) 
Monad m => TraceM (DrawingT u m) 

runDrawingT :: Monad m => DrawingContext -> DrawingT u m a -> m (a, HPrim u)Source

runFdcDrawing :: (Real u, Floating u, FromPtSize u) => DrawingContext -> Drawing u a -> (a, Maybe (Picture u))Source

Run the Drawing generating a Picture within a "font delta context" using the font-family and font-size from the intial DrawingContext.

Using a font delta context can reduce the code size of the generated SVG file (PostScript ignores the FDC).

execFdcDrawing :: (Real u, Floating u, FromPtSize u) => DrawingContext -> Drawing u a -> Maybe (Picture u)Source

exec version of runFdcContext.

runFdcDrawingT :: (Real u, Floating u, FromPtSize u, Monad m) => DrawingContext -> DrawingT u m a -> m (a, Maybe (Picture u))Source

Transformer version of runFdcDrawing.

execFdcDrawingT :: (Real u, Floating u, FromPtSize u, Monad m) => DrawingContext -> DrawingT u m a -> m (Maybe (Picture u))Source

Transformer version of execFdcDrawing.

liftToPictureU :: (Real u, Floating u, FromPtSize u) => HPrim u -> Picture uSource

Unsafe promotion of HPrim to Picture.

If the HPrim is empty, a run-time error is thrown.

liftToPictureMb :: (Real u, Floating u, FromPtSize u) => HPrim u -> Maybe (Picture u)Source

Safe promotion of HPrim to (Maybe Picture).

If the HPrim is empty, then Nothing is returned.

mbPictureU :: (Real u, Floating u, FromPtSize u) => Maybe (Picture u) -> Picture uSource

Unsafe promotion of (Maybe Picture) to Picture.

This is equivalent to:

 fromMaybe (error "empty") $ pic

This function is solely a convenience, using it saves one import and a few characters.

If the supplied value is Nothing a run-time error is thrown.

draw :: (TraceM m, DrawingCtxM m, u ~ MonUnit m) => Graphic u -> m ()Source

Draw a Graphic taking the drawing style from the drawing context.

This operation is analogeous to tell in a Writer monad.

xdraw :: (TraceM m, DrawingCtxM m, u ~ MonUnit m) => XLink -> Graphic u -> m ()Source

Hyperlink version of draw.

drawi :: (TraceM m, DrawingCtxM m, u ~ MonUnit m) => Image u a -> m aSource

Draw an Image taking the drawing style from the drawing context.

The graphic representation of the Image is drawn in the Trace monad, and the result is returned.

xdrawi :: (TraceM m, DrawingCtxM m, u ~ MonUnit m) => XLink -> Image u a -> m aSource

Hyperlink version of drawi.

ati :: LocImage u a -> Point2 u -> Image u aSource

conn :: ConnImage u a -> Point2 u -> LocImage u aSource

nodei :: (TraceM m, DrawingCtxM m, PointSupplyM m, u ~ MonUnit m) => LocImage u a -> m aSource