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

PortabilityGHC
Stabilityhighly unstable
Maintainerstephen.tetley@gmail.com

Wumpus.Basic.Graphic.Base

Contents

Description

Base types for Drawing Objects, Graphics / Images (a Graphic that also returns an answer), etc.

Base classes for monadic drawing.

Notes on prefix and suffix names:

Function types suffixed F are functions from same-to-same, e.g.:

 type Point2F u = Point2 u -> Point2 u

Functional types subfixed R are functions from some static context to the answer type (c.f the ReaderMonad), e.g.:

 newtype DrawingR a = DrawingR { getDrawingR :: DrawingContext -> a }

The suffix M is used for classes defining monadic actions.

The prefix Loc indicates a functional type from Point2 to something...

The prefix ThetaLoc indicates a functional type from Direction (radian) then Point to something...

** WARNING ** - some names are expected to change.

Synopsis

Documentation

class OPlus t whereSource

A Semigroup class.

Methods

oplus :: t -> t -> tSource

Instances

OPlus (Primitive u) 
OPlus (PrimGraphic u) 
OPlus a => OPlus (DrawingR a) 
OPlus a => OPlus (r -> a) 
(OPlus a, OPlus b) => OPlus (a, b) 

oconcat :: OPlus t => t -> [t] -> tSource

anterior :: OPlus t => t -> t -> tSource

superior :: OPlus t => t -> t -> tSource

Drawing monads.

type family MonUnit m :: *Source

DUnit is always for fully saturated type constructors, so (seemingly) an equivalent type family is needed for monads.

class Monad m => TraceM m whereSource

Collect elementary graphics as part of a larger drawing.

TraceM works much like a writer monad.

Methods

trace :: HPrim (MonUnit m) -> m ()Source

Instances

TraceM (Drawing u) 
Monad m => TraceM (DrawingT u m) 
(u ~ MonUnit m, Monad m, TraceM m) => TraceM (TurtleT u m) 
(u ~ MonUnit m, Monad m, TraceM m) => TraceM (ScalingT ux uy u m) 

asksDC :: DrawingCtxM m => (DrawingContext -> a) -> m aSource

Project a value out of a context.

class Monad m => PointSupplyM m whereSource

A monad that supplies points, e.g. a turtle monad.

Methods

position :: u ~ MonUnit m => m (Point2 u)Source

Instances

(u ~ MonUnit m, Monad m, Num u) => PointSupplyM (TurtleT u m) 

Base types

data HPrim u Source

Graphics objects, even simple ones (line, arrow, dot) might need more than one primitive (path or text label) for their construction. Hence, the primary representation that all the others are built upon must support concatenation of primitives.

Wumpus-Core has a type Picture - made from one or more Primitives - but Pictures include support for affine frames. For drawing many simple graphics (dots, connector lines...) that do not need individual affine transformations this is a penalty. A list of Primitives is therefore more suitable representation, and a Hughes list which supports efficient concatenation is wise.

Instances

type Point2F u = Point2 u -> Point2 uSource

Point transformation function.

data DrawingR a Source

Drawings in Wumpus-Basic have an implicit graphics state the DrawingContext, the most primitive building block is a function from the DrawingContext to some polymorphic answer.

This functional type is represented concretely as DrawingR.

 DrawingR :: DrawingContext -> a 

runDrawingR :: DrawingContext -> DrawingR a -> aSource

Run a Drawing Function with the supplied Drawing Context.

type LocGraphic u = Point2 u -> Graphic uSource

Commonly graphics take a start point as well as a drawing context.

Here they are called a LocGraphic - graphic with a (starting) location.

type Image u a = DrawingR (a, PrimGraphic u)Source

Images return a value as well as drawing. A node is a typical example - nodes are drawing but the also support taking anchor points.

type ImageTrafoF u a = Image u a -> Image u aSource

type LocImage u a = Point2 u -> Image u aSource

type ConnectorGraphic u = Point2 u -> Point2 u -> Graphic uSource

ConnectorGraphic is a connector drawn between two points contructing a Graphic.

type ConnectorImage u a = Point2 u -> Point2 u -> Image u aSource

ConnectorImage is a connector drawn between two points constructing an Image.

Usually the answer type of a ConnectorImage will be a Path so the Points ar midway, atstart etc. can be taken on it.

type ThetaLocGraphic u = Radian -> LocGraphic uSource

A function from Radian -\> Point -\> Graphic...