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

PortabilityGHC
Stabilityhighly unstable
Maintainerstephen.tetley@gmail.com

Wumpus.Basic.Graphic.Primitive

Contents

Description

Graphic types and operations.

** WARNING ** - this due a major revision and will change significantly (or disappear...).

Synopsis

Type aliases

type Graphic u = H (Primitive u)Source

Note - this representation allows for zero, one or more Primitives to be collected together.

type GraphicF u = Point2 u -> Graphic uSource

General combinators

cc :: (r1 -> a -> ans) -> (r1 -> r2 -> a) -> r1 -> r2 -> ansSource

Composition operator...

 cc f g = \x y -> f x (g x y)

supply :: u -> (u -> a) -> aSource

Reverse application.

Operations

drawGraphic :: (Real u, Floating u, FromPtSize u) => Graphic u -> Maybe (Picture u)Source

Note - a Picture cannot be empty whereas a Graphic can. Hence this function returns via Maybe.

drawGraphicU :: (Real u, Floating u, FromPtSize u) => Graphic u -> Picture uSource

Unsafe version of drawGraphic - this function throws an error when the graphic is empty.

wrapG :: Primitive u -> Graphic uSource

Lift a Primitive to a Graphic

emptyG :: Graphic uSource

The empty graphic.

Graphic primitives

textline :: Num u => RGBi -> FontAttr -> String -> GraphicF uSource

Text should not contain newlines.

Note the supplied point is the 'left-baseline'.

straightLine :: Fractional u => RGBi -> StrokeAttr -> Vec2 u -> GraphicF uSource

Vector is applied to the point.

strokedRectangle :: Fractional u => RGBi -> StrokeAttr -> u -> u -> GraphicF uSource

Supplied point is center.

filledRectangle :: Fractional u => RGBi -> u -> u -> GraphicF uSource

Supplied point is center.

rectanglePath :: Num u => u -> u -> Point2 u -> PrimPath uSource

Supplied point is bottom-left.

strokedCircle :: Floating u => RGBi -> StrokeAttr -> Int -> u -> GraphicF uSource

strokedCircle : stroked_props * num_subs * radius -> GraphicF

Draw a stroked circle made from Bezier curves. num_subs is the number of subdivisions per quadrant.

The result is a HOF (GraphicF :: Point -> Graphic) where the point is the center.

filledCircle :: Floating u => RGBi -> Int -> u -> GraphicF uSource

filledCircle : fill_props * num_subs * radius -> GraphicF

Draw a filled circle made from Bezier curves. num_subs is the number of subdivisions per quadrant.

The result is a HOF (GraphicF :: Point -> Graphic) where the point is the center.

disk :: Fractional u => RGBi -> u -> GraphicF uSource

disk is drawn with Wumpus-Core's ellipse primitive.

This is a efficient representation of circles using PostScript's arc or SVG's circle in the generated output. However, stroked-circles do not draw well after non-uniform scaling - the line width is scaled as well as the shape.

For stroked circles that can be scaled, consider making the circle from Bezier curves.

Displacement

type Point2T u = Point2 u -> Point2 uSource

positionWith :: Point2T u -> (Point2 u -> a) -> Point2 u -> aSource

disp :: Num u => u -> u -> Point2T uSource

vdisp :: Num u => u -> Point2T uSource

hdisp :: Num u => u -> Point2T uSource

Grid

data Rectangle u Source

Constructors

Rectangle 

Fields

rect_width :: !u
 
rect_height :: !u
 

Instances

Eq u => Eq (Rectangle u) 
Ord u => Ord (Rectangle u) 
Show u => Show (Rectangle u) 

grid :: RealFrac u => RGBi -> StrokeAttr -> u -> u -> Rectangle u -> GraphicF uSource

grid : stroke_props * xstep * ystep * boundary_rect -> GraphicF

The result is a HOF (GraphicF :: Point -> Graphic) where the point is bottom-left.

border :: Num u => RGBi -> StrokeAttr -> Rectangle u -> GraphicF uSource

border : stroke_props * boundary_rect -> GraphicF

The result is a HOF (GraphicF :: Point -> Graphic) where the point is bottom-left.