wumpus-core-0.36.0: Pure Haskell PostScript and SVG generation.

PortabilityGHC
Stabilityhighly unstable
MaintainerStephen Tetley <stephen.tetley@gmail.com>

Wumpus.Core.Picture

Contents

Description

Construction of pictures, paths and text labels.

Synopsis

Construction

frame :: (Real u, Floating u, FromPtSize u) => [Primitive u] -> Picture uSource

Lift a list of primitives to a composite picture.

The order of the list maps to the order of printing - the front of the list is drawn first in the file. This also means that the front of the list is drawn at the back in the Z-Order.

This function throws an error when supplied the empty list.

multi :: (Fractional u, Ord u) => [Picture u] -> Picture uSource

Place multiple pictures within the standard affine frame.

This function throws an error when supplied the empty list.

fontDeltaContext :: FontAttr -> Picture u -> Picture uSource

Update the font delta attributes for SVG output.

Note - fontDeltaContext does not set the font properties of elements in the supplied Picture, it is solely a mechanism to help reduce the code size of the generated SVG by factoring common attributes into a group (g) element. For instance, settting the font properties with fontDeltaContext can eliminate the repeated use of font-family and font-size in this code:

 <text font-family="Helvetica" font-size="12"> ... </text>
 <text font-family="Helvetica" font-size="12"> ... </text>
 <text font-family="Helvetica" font-size="12"> ... </text>

With the appropriate font delta context, this code will be generated:

 <g font-family="Helvetica" font-size="12">
   <text > ... </text>
   <text > ... </text>
   <text > ... </text>
 </g>

Wumpus ignores fontDeltaContext directives when generating PostScript. Unlike SVG, PostScript is not naturally nested, so introducing nesting with gsave and grestore is not likely to improve the PostScript Wumpus generates.

path :: Point2 u -> [PrimPathSegment u] -> PrimPath uSource

Create a Path from a start point and a list of PathSegments.

lineTo :: Point2 u -> PrimPathSegment uSource

lineTo : end_point -> path_segment

Create a straight-line PathSegment, the start point is implicitly the previous point in a path.

curveTo :: Point2 u -> Point2 u -> Point2 u -> PrimPathSegment uSource

curveTo : control_point1 * control_point2 * end_point -> path_segment

Create a curved PathSegment, the start point is implicitly the previous point in a path.

vertexPath :: [Point2 u] -> PrimPath uSource

Convert the list of vertices to a path of straight line segments.

curvedPath :: [Point2 u] -> PrimPath uSource

Convert a list of vertices to a path of curve segments. The first point in the list makes the start point, each curve segment thereafter takes 3 points. Spare points at the end are discarded.

xlinkhref :: String -> XLinkSource

Create a hyperlink for SVG output.

xlinkGroup :: XLink -> [Primitive u] -> Primitive uSource

Create a hyperlinked group of Primitives.

This function throws a runtime error when supplied with an empty list.

primGroup :: [Primitive u] -> Primitive uSource

Group a list of Primitives.

This function throws a runtime error when supplied with an empty list.

Constructing primitives

ostroke :: Num u => RGBi -> StrokeAttr -> PrimPath u -> Primitive uSource

ostroke : rgb * stroke_attr * path -> Primitive

Create a open, stroked path.

cstroke :: Num u => RGBi -> StrokeAttr -> PrimPath u -> Primitive uSource

cstroke : rgb * stroke_attr * path -> Primitive

Create a closed, stroked path.

zostroke :: Num u => PrimPath u -> Primitive uSource

zostroke : path -> Primitive

Create an open, stroked path using the default stroke attributes and coloured black.

zcstroke :: Num u => PrimPath u -> Primitive uSource

zcstroke : path -> Primitive

Create a closed stroked path using the default stroke attributes and coloured black.

fill :: Num u => RGBi -> PrimPath u -> Primitive uSource

fill : rgb * path -> Primitive

Create a filled path.

zfill :: Num u => PrimPath u -> Primitive uSource

zfill : path -> Primitive

Create a filled path coloured black.

fillStroke :: Num u => RGBi -> StrokeAttr -> RGBi -> PrimPath u -> Primitive uSource

fillStroke : fill_rgb * stroke_attr * stroke_rgb * path -> Primitive

Create a closed path that is both filled and stroked (the fill is below in the zorder).

clip :: (Num u, Ord u) => PrimPath u -> Picture u -> Picture uSource

clip : path * picture -> Picture

Clip a picture with respect to the supplied path.

textlabel :: Num u => RGBi -> FontAttr -> String -> Point2 u -> Primitive uSource

textlabel : rgb * font_attr * string * baseline_left -> Primitive

Create a text label. The string should not contain newline or tab characters. Also double-spaces should not be used - a rendering agent for SVG will coalesce double-spaces into a single space. For precise control of spacing and kerning use hkernlabel.

The supplied point is the left baseline.

rtextlabel :: Num u => RGBi -> FontAttr -> String -> Radian -> Point2 u -> Primitive uSource

rtextlabel : rgb * font_attr * string * rotation * baseline_left -> Primitive

Create a text label rotated by the supplied angle about the baseline-left.

The supplied point is the left baseline.

ztextlabel :: Num u => String -> Point2 u -> Primitive uSource

ztextlabel : string * baseline_left -> Primitive

Create a label where the font is Courier, text size is 14pt and colour is black.

hkernlabel :: Num u => RGBi -> FontAttr -> [KerningChar u] -> Point2 u -> Primitive uSource

hkernlabel : rgb * font_attr * kerning_chars * baseline_left -> Primitive

Create a text label with horizontal kerning for each character.

Note - kerning is relative to the left baseline of the previous character, it is *not relative* to the right-hand boundary of the previous char. While the later would be more obvious it would take a lot of effort to implement as it would need access to the metrics encoded in font files.

Characters are expected to be drawn left to right, so displacements should not be negative. If the displacement is zero the character will be drawn ontop of the previous char.

The charcters should not contain newline or tab characters.

The supplied point is the left baseline.

** CAUTION ** - hkernlabel generates a coordinate list for X-positions rather than a single start point. This is perfectly valid SVG, but it is not universally supported by renderers. Chrome support is fine, but Firefox and Safari currently seem lacking.

vkernlabel :: Num u => RGBi -> FontAttr -> [KerningChar u] -> Point2 u -> Primitive uSource

vkernlabel : rgb * font_attr * kerning_chars * baseline_left -> Primitive

Create a text label with vertical kerning for each character - the text is expected to grow downwards.

Note - kerning here is the measure between baselines of sucessive characters, it is *not* the distance between the bottom of one chararter and the top of the next character.

While the later maybe be more obvious from a drawing perspective, it would take a lot of effort to implement as it would need access to the metrics encoded in font files.

Characters are expected to be drawn downwards - a positive number represents the downward displacement - so displacements should not be negative. If the displacement is zero the character will be drawn ontop of the previous char.

The charcters should not contain newline or tab characters.

The supplied point is the left baseline of the top character.

** CAUTION ** - vkernlabel generates a coordinate list for Y-positions rather than a single start point. This is perfectly valid SVG, but it is not universally supported by renderers. Chrome support is fine, but Firefox and Safari currently seem lacking.

kernchar :: u -> Char -> KerningChar uSource

kernchar : displacement * char -> KerningChar

Construct a regular (i.e. non-special) Char along with its displacement from the left-baseline of the previous Char.

kernEscInt :: u -> Int -> KerningChar uSource

kernEscInt : displacement * char_code -> KerningChar

Construct a Char by its character code along with its displacement from the left-baseline of the previous Char.

kernEscName :: u -> String -> KerningChar uSource

kernEscName : displacement * char_name -> KerningChar

Construct a Char by its character name along with its displacement from the left-baseline of the previous Char.

strokeEllipse :: Num u => RGBi -> StrokeAttr -> u -> u -> Point2 u -> Primitive uSource

strokeEllipse : rgb * stroke_attr * rx * ry * center -> Primtive

Create a stroked ellipse.

Note - within Wumpus, ellipses are considered an unfortunate but useful optimization. Drawing good cicles with Beziers needs at least eight curves, but drawing them with PostScript's arc command needs a single operation. For drawings with many dots (e.g. scatter plots) it seems sensible to employ this optimization.

A deficiency of Wumpus's ellipse is that (non-uniformly) scaling a stroked ellipse also (non-uniformly) scales the pen it is drawn with. Where the ellipse is wider, the pen stroke will be wider too.

Avoid non-uniform scaling stroked ellipses!

rstrokeEllipse :: Num u => RGBi -> StrokeAttr -> u -> u -> Radian -> Point2 u -> Primitive uSource

rstrokeEllipse : rgb * stroke_attr * rx * ry * rotation * center -> Primtive

Create a stroked ellipse rotated about the center by theta.

fillEllipse :: Num u => RGBi -> u -> u -> Point2 u -> Primitive uSource

fillEllipse : rgb * stroke_attr * rx * ry * center -> Primtive

Create a filled ellipse.

rfillEllipse :: Num u => RGBi -> u -> u -> Radian -> Point2 u -> Primitive uSource

rfillEllipse : colour * stroke_attr * rx * ry * rotation * center -> Primtive

Create a filled ellipse rotated about the center by theta.

zellipse :: Num u => u -> u -> Point2 u -> Primitive uSource

zellipse : rx * ry * center -> Primtive

Create a black, filled ellipse.

fillStrokeEllipse :: Num u => RGBi -> StrokeAttr -> RGBi -> u -> u -> Point2 u -> Primitive uSource

fillStrokeEllipse : fill_rgb * stroke_attr * stroke_rgb * rx * ry * center -> Primtive

Create a bordered (i.e. filled and stroked) ellipse.

rfillStrokeEllipse :: Num u => RGBi -> StrokeAttr -> RGBi -> u -> u -> Radian -> Point2 u -> Primitive uSource

rfillStrokeEllipse : fill_rgb * stroke_attr * stroke_rgb * rx * ry * theta * center -> Primtive

Create a bordered (i.e. filled and stroked) ellipse rotated about the center by theta.

Operations

extendBoundary :: (Num u, Ord u) => u -> u -> Picture u -> Picture uSource

extendBoundary : x * y * picture -> Picture

Extend the bounding box of a picture.

The bounding box is both horizontal directions by x and both vertical directions by y. x and y must be positive This function cannot be used to shrink a boundary.

Picture composition

picOver :: (Num u, Ord u) => Picture u -> Picture u -> Picture uSource

picOver : picture * picture -> Picture

Draw the first picture on top of the second picture - neither picture will be moved.

picMoveBy :: (Num u, Ord u) => Picture u -> Vec2 u -> Picture uSource

picMoveBy : picture * vector -> Picture

Move a picture by the supplied vector.

picBeside :: (Num u, Ord u) => Picture u -> Picture u -> Picture uSource

picBeside : picture * picture -> Picture

Move the second picture to sit at the right side of the first picture

Illustrating pictures and primitives

printPicture :: (Num u, PSUnit u) => Picture u -> IO ()Source

Print the syntax tree of a Picture to the console.

illustrateBounds :: (Real u, Floating u, FromPtSize u) => RGBi -> Picture u -> Picture uSource

illustrateBounds : bbox_rgb * picture -> Picture

Draw the picture on top of an image of its bounding box. The bounding box image will be drawn in the supplied colour.

illustrateBoundsPrim :: (Real u, Floating u, FromPtSize u) => RGBi -> Primitive u -> Picture uSource

illustrateBoundsPrim : bbox_rgb * primitive -> Picture

Draw the primitive on top of an image of its bounding box. The bounding box image will be drawn in the supplied colour.

The result will be lifted from Primitive to Picture.

illustrateControlPoints :: (Real u, Floating u, FromPtSize u) => RGBi -> Primitive u -> Picture uSource

illustrateControlPoints : control_point_rgb * primitive -> Picture

Generate the control points illustrating the Bezier curves within a picture.

This has no effect on TextLabels. Nor does it draw Beziers of a hyperlinked object.

Pseudo control points are generated for ellipses, although strictly speaking ellipses do not use Bezier curves - they are implemented with PostScript's arc command.