diagrams-0.2.2.3: An EDSL for creating simple diagrams

Portabilityportable
Stabilityexperimental
Maintainerbyorgey@gmail.com

Graphics.Rendering.Diagrams

Contents

Description

An embedded domain-specific language (EDSL) for creating simple diagrams, illustrations, and other types of graphics, built on top of the Cairo rendering engine.

Synopsis

Introduction

Graphics.Rendering.Diagrams is an embedded domain-specific language (EDSL) for creating simple graphics. It is compositional; starting with some basic shapes, you can build up complex diagrams by combining simpler diagrams in various ways.

A few fundamental concepts to keep in mind:

  • When constructing diagrams, there is no concept of an absolute coordinate system, although each diagram does have a local coordinate system.
  • Every diagram has an associated rectangular bounding box, which determines its positioning and alignment relative to other diagrams. Usually this makes no difference but there are times when it's nice to be aware of it. For example, translating a diagram works by moving the diagram relative to its bounding box; positioning the bounding box where it would have gone means the diagram itself ends up elsewhere. To visualize bounding boxes, you can use the showBBox and showBBoxes functions.
  • The positive y-axis points downwards. This also means that positive rotations are clockwise.

For some simple examples, see http://code.haskell.org/diagrams/.

Enjoy! Please send comments, suggestions, bug reports, or patches to byorgey at cis dot upenn dot edu.

Primitives

data Diagram Source

Diagram is the core data type which describes a diagram. Diagrams may be constructed, transformed, combined, and ultimately rendered as an image.

nil :: DiagramSource

The nil diagram, which takes up no space and produces no output.

Shapes

circle :: Double -> DiagramSource

circle r is a circle with radius r.

arc :: Double -> Double -> Double -> DiagramSource

arc r a1 a2 is a circular arc with radius r, starting at angle a1*2*pi and proceeding in a direction of increasing angle to a2*2*pi.

rectPath :: Double -> Double -> PathSource

rectPath w h is a closed path describing a rectangle of width w and height h.

rect :: Double -> Double -> DiagramSource

rect w h is a rectangle of width w and height h.

roundRect :: Double -> Double -> DiagramSource

roundRect w h is a rectangle of width w and height h with rounded corners having a radius one third the length of the shortest edge.

roundRectF :: Double -> Double -> Double -> DiagramSource

roundRect w h f is a rectangle of width w and height h with rounded corners having a radius f times the length of the shortest edge.

regPolyPath :: Int -> Double -> PathSource

regPolyPath n r is an open path corresponding to a regular polygon, with the first vertex oriented along the positive x-axis and proceeding clockwise.

regPoly :: Int -> Double -> DiagramSource

regPoly n r is a regular n-gon, with a circumcircle of radius r. One vertex is oriented along the positive x-axis.

rotRegPoly :: Int -> Double -> Double -> DiagramSource

rotRegPoly n r a is the same as regPoly n r but rotated through an angle of a*2*pi radians (i.e., a represents a fraction of an entire revolution). This is different than rotate a $ regPoly n r; rotRegPoly will adjust the bounding box correctly (using rotPath), whereas the construction using rotate will still have a bounding box corresponding to the unrotated polygon.

shape :: ShapeClass s => s -> DiagramSource

Create a Diagram out of any instance of ShapeClass.

rawCairo :: Point -> Render () -> DiagramSource

rawCairo s r is a diagram with bounding box size s, rendered by executing Cairo Render action r. Import Graphics.Rendering.Cairo to access Cairo operations.

text :: Double -> String -> DiagramSource

Create text with black fill, no outline, and a default font.

textPath :: Double -> String -> DiagramSource

textPath s t is a string of text t at size s, represented as an outline with separate stroke and fill.

Spacers

hspace :: Double -> DiagramSource

hspace w is a Diagram which produces no output but takes up w amount of space horizontally. Useful for manually creating horizontal separation between two diagrams. A negative value of w can also be used to move two diagrams closer to one another. hspace w is equivalent to empty w 0.

vspace :: Double -> DiagramSource

vspace h is a Diagram which produces no output but takes up h amount of space vertically. Useful for manually creating vertical separation between two diagrams. A negative value of h can also be used to move two diagrams closer to one another. vspace h is equivalent to empty 0 h.

empty :: Double -> Double -> DiagramSource

empty w h is an empty diagram which produces no output, but takes up an amount of space equal to a w by h rectangle.

Paths

data Path Source

A path is a series of edges which can be stroked, filled, etc. It can be either open (the default) or closed (i.e. the first and last vertices are connected).

Instances

emptyPath :: PathSource

The empty path, i.e. a path with no edges.

pathFromVertices :: [Point] -> PathSource

Create an open path from a list of vertices. For example, pathFromVertices [(1,3), (4,4), (6,5)] describes the path with two segments which starts at (1,3), has a corner at (4,4), and ends at (6,5). Note, however, that the vertices themselves are not significant, only the distances between them. That is, pathFromVertices [(0,1), (3,2), (5,3)] describes exactly the same path.

pathFromVectors :: [Vec] -> PathSource

Create an open path from a list of edge displacement vectors. For example, pathFromVectors [(1,1), (3,4)] describes the path with two segments which first moves one unit in the positive x and y directions, and then moves three units in the positive x direction and four in the positive y direction.

pathToVertices :: Point -> Path -> [Point]Source

Convert a path into a list of vertices, starting with the given vertex.

pathToVectors :: Path -> [Vec]Source

Convert a path to a list of vectors corresponding to the edges of the path.

pathConcat :: Path -> Path -> PathSource

Concatenate two open paths into a single open path consisting of the first followed by the second.

closed :: Path -> PathSource

Create a closed path (by connecting the first and last points in the path).

isClosed :: Path -> BoolSource

Determine whether a Path is closed or open.

rotPath :: Double -> Path -> PathSource

Rotate a path by a fraction of a circle. rotPath d rotates paths by an angle of d*2*pi radians. Note that creating a Diagram from a Path (using straight or curved or some other such function) and then applying rotate to it is different than first applying rotPath to the Path before making it into a Diagram. In the latter case, the bounding box will be correct, whereas in the former case, the bounding box will still correspond to the unrotated version of the path.

straight :: Path -> DiagramSource

straight creates a Diagram from a path, by drawing straight lines along the path edges.

curved :: Double -> Path -> DiagramSource

curved d p is a curved path which follows generally the path p. The parameter d specifies the amount of corner rounding. In particular, d should be a value between 0 and 1, which specifies what fraction of the path segments should be rounded off with bezier curves, using the path vertices as control points. Thus d = 0 produces the polygonal path itself, with no curved segments; d = 1 produces a continuously curving path tangent to the midpoints of the path segments; and intermediate values of d interpolate between the two. The curved path produced will be everywhere differentiable as long as d > 0. If the path is not closed, the curve will begin and end at the first and last path vertices (no rounding will take place at these vertices).

Combinators

Various ways to combine Diagrams into larger Diagrams.

Union

(##) :: Diagram -> Diagram -> DiagramSource

Superimpose one diagram atop another. d1 ## d2 results in a diagram in which d2 is on top of d1 (i.e., d1 is drawn first, then d2).

union :: [Diagram] -> DiagramSource

Create a Diagram as a union of subdiagrams which will not be repositioned. If the subdiagrams overlap, they will appear with the first Diagram on the bottom, and the last on top.

unionA :: HAlignment -> VAlignment -> [Diagram] -> DiagramSource

Create a Diagram as a union of subdiagrams superimposed on one another, aligned vertically and/or horizontally.

Lists

(<>) :: Diagram -> Diagram -> DiagramSource

d1 <> d2 is a Diagram with d1 to the left of d2, aligned along their top edges.

(//) :: Diagram -> Diagram -> DiagramSource

d1 // d2 is a Diagram with d1 above d2, aligned along their left edges.

hcat :: [Diagram] -> DiagramSource

Lay out a list of Diagrams horizontally from left to right, aligned along their top edges.

vcat :: [Diagram] -> DiagramSource

Lay out a list of Diagrams vertically from top to bottom, aligned along their left edges.

hcatA :: VAlignment -> [Diagram] -> DiagramSource

Lay out a list of Diagrams horizontally from left to right, with the given vertical alignment (top, vcenter, or bottom).

vcatA :: HAlignment -> [Diagram] -> DiagramSource

Lay out a list of Diagrams vertically from top to bottom, with the given horizontal alignment (left, hcenter, or right).

hsepSource

Arguments

:: Double

amount of separation between each pair of diagrams

-> [Diagram] 
-> Diagram 

Lay out a list of Diagrams horizontally, aligned along their top edges, with a given amount of separation in between each pair.

vsepSource

Arguments

:: Double

amount of separation between each pair of diagrams

-> [Diagram] 
-> Diagram 

Lay out a list of Diagrams vertically, aligned along their left edges, with a given amount of separation in between each pair.

hsepASource

Arguments

:: Double

amount of separation between each pair of diagrams

-> VAlignment

alignment to use (top, vcenter, or bottom)

-> [Diagram] 
-> Diagram 

Lay out a list of Diagrams horizontally, with the given amount of separation in between each pair, using the given vertical alignment (top, vcenter, or bottom).

vsepASource

Arguments

:: Double

amount of separation between each pair of diagrams

-> HAlignment

alignment to use (left, hcenter, or right)

-> [Diagram] 
-> Diagram 

Lay out a list of Diagrams vertically, with the given amount of separation in between each pair, using the given horizontal alignment (left, hcenter, or right).

hdistribSource

Arguments

:: Double

How far from one diagram to the next?

-> HAlignment

Distribute according to which parts of the diagrams (left, hcenter, right)?

-> [Diagram] 
-> Diagram 

Distribute a list of Diagrams horizontally according to a regular spacing, aligned along their top edges.

vdistribSource

Arguments

:: Double

How far from one diagram to the next?

-> VAlignment

Distribute according to which parts of the diagrams (top, vcenter, bottom)?

-> [Diagram] 
-> Diagram 

Distribute a list of Diagrams vertically according to a regular spacing, aligned along their left edges.

hdistribASource

Arguments

:: Double

How far from one diagram to the next?

-> HAlignment

Distribute according to which parts of the diagrams (left, hcenter, right)?

-> VAlignment

alignment to use (top, vcenter, bottom)

-> [Diagram] 
-> Diagram 

Distribute a list of Diagrams horizontally according to a regular spacing, with the given alignment.

vdistribASource

Arguments

:: Double

How far from one diagram to the next?

-> VAlignment

Distribute according to which parts of the diagrams (top, vcenter, bottom)?

-> HAlignment

alignment to use (left, hcenter, right)

-> [Diagram] 
-> Diagram 

Distribute a list of Diagrams vertically according to a regular spacing, with the given alignment.

position :: [(Point, Diagram)] -> DiagramSource

Create a diagram from a list of subdiagrams with explicit positions in a local coordinate system. Each subdiagram will be positioned with its center at the corresponding position. position is equivalent to positionA hcenter vcenter.

positionA :: HAlignment -> VAlignment -> [(Point, Diagram)] -> DiagramSource

Create a diagram from a list of subdiagrams with explicit positions in a local coordinate system. The alignment options specify what part of each subdiagram should be placed on the corresponding position. For example, positionA left top will position the top left corner of each subdiagram at the corresponding point.

positionAlong :: [Diagram] -> Path -> DiagramSource

Create a diagram from a list of subdiagrams and a given path, by positioning the subdiagrams at successive vertices of the path. If there are more diagrams than path vertices, the extra diagrams will be discarded.

positionAlongA :: HAlignment -> VAlignment -> [Diagram] -> Path -> DiagramSource

A version of positionAlong with explicit alignment.

grid :: [[Diagram]] -> DiagramSource

Align diagrams into a grid, with each item centered horizontally and vertically Warning: there is currently an exponential performace blowup if you nest grids. (exponential in how deep the nesting is).

gridA :: HAlignment -> VAlignment -> [[Diagram]] -> DiagramSource

Align diagrams into a grid with each item aligned as specified. Warning: there is currently an exponential performace blowup if you nest grids (exponential in how deep the nesting is).

gridAs :: [[(HAlignment, VAlignment)]] -> [[Diagram]] -> DiagramSource

Align diagrams into a grid, specifying individual alignments for each item. Warning: there is currently an exponential performace blowup if you nest grids (exponential in how deep the nesting is).

type VAlignment = AlignmentSource

Vertical alignment.

type HAlignment = AlignmentSource

Horizontal alignment.

Complex layouts

treeSource

Arguments

:: Double

separation between layers

-> Double

separation between siblings

-> Tree Diagram 
-> Diagram 

Lay out a Tree (from Data.Tree) of Diagrams in a top-down fashion. This layout is experimental; future releases of the Diagrams library are planned which will be able to automatically draw edges between nodes in the tree.

Miscellaneous

pad :: Double -> Double -> Diagram -> DiagramSource

Add extra padding to a diagram. pad w h d is a diagram which is the same as d, but with w units added to the width and h units added to the height, with d centered in the available space. Thus pad w h is equivalent to padA w h hcenter vcenter.

padA :: Double -> Double -> HAlignment -> VAlignment -> Diagram -> DiagramSource

Add extra padding to a diagram, aligning the diagram as indicated within the avilable space.

showBBox :: Diagram -> DiagramSource

Show a rectangle denoting a diagram's bounding box, in addition to the diagram itself.

showBBoxes :: Diagram -> DiagramSource

Show the bounding boxes of a diagram and all its subdiagrams.

withSizeSource

Arguments

:: (Double -> Double -> Diagram)

Function for new diagram

-> Diagram

Old diagram

-> Diagram 

Create one diagram using the current size of another. The new diagram is returned, the old one is discarded.

Transformations

Various ways to modify and transform Diagrams.

stretch :: Double -> Double -> Diagram -> DiagramSource

Stretch a diagram by a separate scaling factor for each axis. stretch w h scales by a factor of w in the x direction and a factor of h in the y direction.

scale :: Double -> Diagram -> DiagramSource

Scale by the same scaling factor in both dimensions, so the diagram retains its aspect ratio.

scaleX :: Double -> Diagram -> DiagramSource

Scale a diagram along the x-axis only. scaleX s is equivalent to stretch s 1.

scaleY :: Double -> Diagram -> DiagramSource

Scale a diagram along the y-axis only. scaleY s is equivalent to stretch 1 s.

translate :: Double -> Double -> Diagram -> DiagramSource

Translate a diagram by the given relative offsets in the x and y directions. Note that the positive x-axis is to the right, while the positive y-axis points downwards.

translateX :: Double -> Diagram -> DiagramSource

Translate a diagram along the x-axis only. translateX x is equivalent to translate x 0.

translateY :: Double -> Diagram -> DiagramSource

Translate a diagram along the y-axis only. translateY y is equivalent to translate 0 y.

rotate :: Double -> Diagram -> DiagramSource

rotate f rotates a diagram clockwise by fraction f of a complete revolution. rotate f is equivalent to rotateR (2*pi*f).

rotateR :: Double -> Diagram -> DiagramSource

rotateR r rotates a diagram clockwise by r radians.

view :: Point -> Point -> Diagram -> DiagramSource

Explicitly set a diagram's bounding box, by giving the coordinates of the upper left and lower right corners (keeping in mind that the positive y-axis points downwards). Particularly useful for applying to the top-level diagram in order to only view a portion of it in the rendered output.

Attributes

Attributes which affect the way in which a Diagram is rendered.

Colors

Diagrams depends on the Data.Colour library (available on Hackage as the "colour" package) for colo(u)r. Any functions expecting a color can take any instance of the Color type class, which has instances for both the Data.Colour.Colour and Data.Colour.AlphaColour types from Data.Colour.

For normal use, you can just use color names from Data.Colour.Names, which is re-exported by Graphics.Rendering.Diagrams for convenience. For more sophisticated color manipulation, use the facilities provided by the Data.Colour library. For example, to create a color directly from RGB values, you can use the rgb function from Data.Colour.SRGB.Linear.

class Color c Source

The Color type class encompasses color representations which can be used by the Diagrams library; that is, every function in the Diagrams library which expects a color can take any type which is an instance of Color. Instances are provided for both the Colour and AlphaColour types from the Data.Colour library.

Instances

fillColor :: Color c => c -> Diagram -> DiagramSource

Draw a diagram using the given fill color. Note that the new color only applies to parts of the diagram which are not otherwise colored; subdiagrams which already have an explicit fill color will not be affected. The default fill color is completely transparent.

fc :: Color c => c -> Diagram -> DiagramSource

fc is provided as a convenient short synonym for fillColor.

lineColor :: Color c => c -> Diagram -> DiagramSource

Draw a diagram using the given color for lines. Note that the new color only applies to parts of the diagram which are not otherwise colored; subdiagrams which already have an explicit line color will not be affected. The default line color is black.

lc :: Color c => c -> Diagram -> DiagramSource

lc is provided as a convenient short synonym for lineColor.

Other attributes

lineWidth :: Double -> Diagram -> DiagramSource

Draw shape outlines and lines with the given width. Note that the line width is invariant under uniform scaling, although under non-uniform scaling (scaling by different amounts in the x and y axes) lines can become distorted. The default line width is 1.

lw :: Double -> Diagram -> DiagramSource

lw is provided as a convenient short synonym for lineWidth.

lineCap :: LineCap -> Diagram -> DiagramSource

Set the line cap style. Valid values for LineCap are LineCapButt, LineCapRound, and LineCapSquare.

data LineCap

Specify line endings.

LineCapButt
Start(stop) the line exactly at the start(end) point.
LineCapRound
Use a round ending, the center of the circle is the end point.
LineCapSquare
Use squared ending, the center of the square is the end point

lineJoin :: LineJoin -> Diagram -> DiagramSource

Set the line join style. Valid values for LineJoin are LineJoinMiter, LineJoinRound, and LineJoinBevel.

data LineJoin

Specify how lines join.

dashingSource

Arguments

:: [Double]

a list specifying alternate lengths of on and off portions of the stroke. The empty list indicates no dashing.

-> Double

an offset into the dash pattern at which the stroke should start

-> Diagram 
-> Diagram 

Set the line dashing pattern.

typeface :: String -> Diagram -> DiagramSource

Change the default typeface to one named.

tf :: String -> Diagram -> DiagramSource

Convenience function to change the typeface.

Rendering

Rendering diagrams to a file is accomplished with the renderAs function. renderPagesAs renders multiple diagrams as multiple pages for suitable backends. renderOverPNG also provides a specialized rendering method, which overlays a rendererd diagram on top of an existing PNG.

renderAsSource

Arguments

:: OutputType

The output type to use (PNG, PS, PDF, or SVG)

-> String

The name of the file to create.

-> SizeSpec

The desired width or height of the image.

-> Diagram

The diagram to render.

-> IO () 

Render a diagram to a file.

renderPagesAsSource

Arguments

:: OutputType

The output type to use (PS or PDF)

-> String

The name of the file to create.

-> SizeSpec

The desired width or height of the image.

-> [Diagram]

The diagram to render.

-> IO () 

Render a list of diagrams as separate pages to a file.

data OutputType Source

The supported output file types for rendered diagrams.

Constructors

PNG 
PS 
PDF 
SVG 

data SizeSpec Source

A specification of the size of a rendered Diagram.

Constructors

Width Double

an explicit width; the height is determined automatically

Height Double

an explicit height; the width is determined automatically

Auto

determine the size automatically (do not scale)

renderOverPNG :: FilePath -> FilePath -> Diagram -> IO ()Source

renderOverPNG infile outfile d reads the PNG infile and renders d over this, saving the output as a PNG to outfile.