diagrams-lib-0.3: Embedded domain-specific language for declarative graphics

Maintainerdiagrams-discuss@googlegroups.com

Diagrams.TwoD

Contents

Description

This module defines the two-dimensional vector space R^2, two-dimensional transformations, and various predefined two-dimensional shapes. This module re-exports useful functionality from a group of more specific modules:

Synopsis

R^2

type R2 = (Double, Double)Source

The two-dimensional Euclidean vector space R^2.

type P2 = Point R2Source

Points in R^2.

type T2 = Transformation R2Source

Transformations in R^2.

unitX :: R2Source

The unit vector in the positive X direction.

unitY :: R2Source

The unit vector in the positive Y direction.

unit_X :: R2Source

The unit vector in the negative X direction.

unit_Y :: R2Source

The unit vector in the negative Y direction.

direction :: R2 -> CircleFracSource

Compute the direction of a vector, measured counterclockwise from the positive x-axis as a fraction of a full turn. The zero vector is arbitrarily assigned the direction 0.

Angles

tau :: Floating a => aSource

The circle constant, i.e. the ratio of a circle's circumference to its radius. See http://tauday.com/.

class Num a => Angle a whereSource

Type class for types that measure angles.

Methods

toCircleFrac :: a -> CircleFracSource

Convert to a fraction of a circle.

fromCircleFrac :: CircleFrac -> aSource

Convert from a fraction of a circle.

Instances

Angle Deg

360 degrees = 1 full circle.

Angle Rad

tau radians = 1 full circle.

Angle CircleFrac 

newtype CircleFrac Source

Newtype wrapper used to represent angles as fractions of a circle. For example, 13 = tau3 radians = 120 degrees.

Constructors

CircleFrac 

newtype Rad Source

Newtype wrapper for representing angles in radians.

Constructors

Rad 

Fields

getRad :: Double
 

Instances

newtype Deg Source

Newtype wrapper for representing angles in degrees.

Constructors

Deg 

Fields

getDeg :: Double
 

Instances

fullCircle :: Angle a => aSource

An angle representing a full circle.

convertAngle :: (Angle a, Angle b) => a -> bSource

Convert between two angle representations.

Paths

Stroking

stroke :: Renderable (Path R2) b => Path R2 -> Diagram b R2Source

Convert a path into a diagram. The resulting diagram has the names 0, 1, ... assigned to each of the path's vertices.

See also stroke', which takes an extra options record allowing its behavior to be customized.

Note that a bug in GHC 7.0.1 causes a context stack overflow when inferring the type of stroke. The solution is to give a type signature to expressions involving stroke, or (recommended) upgrade GHC (the bug is fixed in 7.0.2 onwards).

stroke' :: (Renderable (Path R2) b, Atomic a) => StrokeOpts a -> Path R2 -> Diagram b R2Source

A variant of stroke that takes an extra record of options to customize its behavior. In particular:

  • Names can be assigned to the path's vertices

StrokeOpts is an instance of Default, so stroke' with { ... } syntax may be used.

strokeT :: Renderable (Path R2) b => Trail R2 -> Diagram b R2Source

A composition of stroke and pathFromTrail for conveniently converting a trail directly into a diagram.

Note that a bug in GHC 7.0.1 causes a context stack overflow when inferring the type of stroke and hence of strokeT as well. The solution is to give a type signature to expressions involving strokeT, or (recommended) upgrade GHC (the bug is fixed in 7.0.2 onwards).

strokeT' :: (Renderable (Path R2) b, Atomic a) => StrokeOpts a -> Trail R2 -> Diagram b R2Source

A composition of stroke' and pathFromTrail for conveniently converting a trail directly into a diagram.

data StrokeOpts a Source

A record of options that control how a path is stroked. StrokeOpts is an instance of Default, so a StrokeOpts records can be created using with { ... } notation.

Constructors

StrokeOpts 

Fields

vertexNames :: [[a]]

Atomic names that should be assigned to the vertices of the path so that they can be referenced later. If there are not enough names, the extra vertices are not assigned names; if there are too many, the extra names are ignored. Note that this is a list of lists of names, since paths can consist of multiple trails. The first list of names are assigned to the vertices of the first trail, the second list to the second trail, and so on.

The default value is the empty list.

Instances

Clipping

clipBy :: (HasStyle a, V a ~ R2) => Path R2 -> a -> aSource

Clip a diagram by the given path:

  • Only the parts of the diagram which lie in the interior of the path will be drawn.
  • The bounding function of the diagram is unaffected.

Shapes

Rules

hrule :: (PathLike p, V p ~ R2) => Double -> pSource

Create a centered horizontal (L-R) line of the given length.

vrule :: (PathLike p, V p ~ R2) => Double -> pSource

Create a centered vertical (T-B) line of the given length.

Circle-ish things

unitCircle :: (Backend b R2, Renderable Ellipse b) => Diagram b R2Source

A circle of radius 1, with center at the origin.

circle :: (Backend b R2, Renderable Ellipse b) => Double -> Diagram b R2Source

A circle of the given radius, centered at the origin.

ellipse :: (Backend b R2, Renderable Ellipse b) => Double -> Diagram b R2Source

ellipse e constructs an ellipse with eccentricity e by scaling the unit circle in the X direction. The eccentricity must be within the interval [0,1).

ellipseXY :: (Backend b R2, Renderable Ellipse b) => Double -> Double -> Diagram b R2Source

ellipseXY x y creates an axis-aligned ellipse, centered at the origin, with radius x along the x-axis and radius y along the y-axis.

arc :: (Angle a, PathLike p, V p ~ R2) => a -> a -> pSource

Given a start angle s and an end angle e, arc s e is the path of a radius one arc counterclockwise between the two angles.

General polygons

polygon :: (PathLike p, V p ~ R2) => PolygonOpts -> pSource

Create a closed regular polygon from the given options.

polygonVertices :: PolygonOpts -> [P2]Source

Generate the vertices of a regular polygon from the given options.

data PolygonOpts Source

Constructors

PolygonOpts 

Fields

sides :: Int

Number of sides; the default is 5.

edgeSkip :: Int

Create star polygons by setting the edge skip to some number other than 1 (the default). With an edge skip of n, edges will connect every nth vertex.

orientation :: PolygonOrientation

Determine how the polygon should be oriented.

data PolygonOrientation Source

Determine how a polygon should be oriented.

Constructors

NoOrient

No special orientation; one vertex will be at (1,0). This is the default.

OrientToX

Orient so the botommost edge is parallel to the x-axis.

OrientToY

Orient so the leftmost edge is parallel to the y-axis.

Special polygons

unitSquare :: (Transformable p, PathLike p, V p ~ R2) => pSource

A sqaure with its center at the origin and sides of length 1, oriented parallel to the axes.

square :: (PathLike p, Transformable p, V p ~ R2) => Double -> pSource

A sqaure with its center at the origin and sides of the given length, oriented parallel to the axes.

rect :: (PathLike p, Transformable p, V p ~ R2) => Double -> Double -> pSource

rect w h is an axis-aligned rectangle of width w and height h, centered at the origin.

starPolygon :: (PathLike p, Transformable p, V p ~ R2) => Int -> Int -> pSource

starPolygon p q creates a star polygon, where p indicates the number of vertices, and an edge connects every qth vertex.

eqTriangle :: (PathLike p, Transformable p, V p ~ R2) => pSource

An equilateral triangle, with radius 1 and base parallel to the x-axis.

Other shapes

roundedRect :: (PathLike p, V p ~ R2) => R2 -> Double -> pSource

roundedRect v r generates a closed trail, or closed path centered at the origin, of an axis-aligned rectangle with diagonal v and circular rounded corners of radius r. r must be between 0 and half the smaller dimension of v, inclusive; smaller or larger values of r will be treated as 0 or half the smaller dimension of v, respectively. The trail or path begins with the right edge and proceeds counterclockwise.

Text

text :: Renderable Text b => String -> Diagram b R2Source

Create a primitive text diagram from the given string, which takes up no space. By default, the text is centered with respect to its local origin (see alignText).

font :: HasStyle a => String -> a -> aSource

Specify a font family to be used for all text within a diagram.

fontSize :: HasStyle a => Double -> a -> aSource

Set the font size, that is, the size of the font's em-square as measured within the current local vector space. The default size is 1.

italic :: HasStyle a => a -> aSource

Set all text in italics.

oblique :: HasStyle a => a -> aSource

Set all text using an oblique slant.

bold :: HasStyle a => a -> aSource

Set all text using a bold font weight.

Images

image :: Renderable Image b => FilePath -> Double -> Double -> Diagram b R2Source

Take an external image from the specified file and turn it into a diagram with the specified width and height, centered at the origin. Note that the image's aspect ratio will be preserved; if the specified width and height have a different ratio than the image's aspect ratio, there will be extra space in one dimension.

Transformations

Rotation

rotation :: Angle a => a -> T2Source

Create a transformation which performs a rotation by the given angle. See also rotate.

rotate :: (Transformable t, V t ~ R2, Angle a) => a -> t -> tSource

Rotate by the given angle. Positive angles correspond to counterclockwise rotation, negative to clockwise. The angle can be expressed using any type which is an instance of Angle. For example, rotate (14 :: 'CircleFrac')@, @rotate (pi2 :: Rad), and rotate (90 :: Deg) all represent the same transformation, namely, a counterclockwise rotation by a right angle.

Note that writing rotate (1/4), with no type annotation, will yield an error since GHC cannot figure out which sort of angle you want to use. In this common situation you can use rotateBy, which is specialized to take a CircleFrac argument.

rotateBy :: (Transformable t, V t ~ R2) => CircleFrac -> t -> tSource

A synonym for rotate, specialized to only work with CircleFrac arguments; it can be more convenient to write rotateBy (14)@ than @'rotate' (14 :: CircleFrac).

rotationAbout :: Angle a => P2 -> a -> T2Source

rotationAbout p is a rotation about the point p (instead of around the local origin).

rotateAbout :: (Transformable t, V t ~ R2, Angle a) => P2 -> a -> t -> tSource

rotateAbout p is like rotate, except it rotates around the point p instead of around the local origin.

Scaling

scalingX :: Double -> T2Source

Construct a transformation which scales by the given factor in the x (horizontal) direction.

scaleX :: (Transformable t, V t ~ R2) => Double -> t -> tSource

Scale a diagram by the given factor in the x (horizontal) direction. To scale uniformly, use Graphics.Rendering.Diagrams.Transform.scale.

scalingY :: Double -> T2Source

Construct a transformation which scales by the given factor in the y (vertical) direction.

scaleY :: (Transformable t, V t ~ R2) => Double -> t -> tSource

Scale a diagram by the given factor in the y (vertical) direction. To scale uniformly, use Graphics.Rendering.Diagrams.Transform.scale.

scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation v

Create a uniform scaling transformation.

scale :: (Transformable t, Fractional (Scalar (V t))) => Scalar (V t) -> t -> t

Scale uniformly in every dimension by the given scalar.

scaleToX :: (Boundable t, Transformable t, V t ~ R2) => Double -> t -> tSource

scaleToX w scales a diagram in the x (horizontal) direction by whatever factor required to make its width w. scaleToX should not be applied to diagrams with a width of 0, such as vrule.

scaleToY :: (Boundable t, Transformable t, V t ~ R2) => Double -> t -> tSource

scaleToY h scales a diagram in the y (vertical) direction by whatever factor required to make its height h. scaleToY should not be applied to diagrams with a width of 0, such as hrule.

Translation

translationX :: Double -> T2Source

Construct a transformation which translates by the given distance in the x (horizontal) direction.

translateX :: (Transformable t, V t ~ R2) => Double -> t -> tSource

Translate a diagram by the given distance in the x (horizontal) direction.

translationY :: Double -> T2Source

Construct a transformation which translates by the given distance in the y (vertical) direction.

translateY :: (Transformable t, V t ~ R2) => Double -> t -> tSource

Translate a diagram by the given distance in the y (vertical) direction.

translation :: HasLinearMap v => v -> Transformation v

Create a translation.

translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> t

Translate by a vector.

Reflection

reflectionX :: T2Source

Construct a transformation which flips a diagram from left to right, i.e. sends the point (x,y) to (-x,y).

reflectX :: (Transformable t, V t ~ R2) => t -> tSource

Flip a diagram from left to right, i.e. send the point (x,y) to (-x,y).

reflectionY :: T2Source

Construct a transformation which flips a diagram from top to bottom, i.e. sends the point (x,y) to (x,-y).

reflectY :: (Transformable t, V t ~ R2) => t -> tSource

Flip a diagram from top to bottom, i.e. send the point (x,y) to (x,-y).

reflectionAbout :: P2 -> R2 -> T2Source

reflectionAbout p v is a reflection in the line determined by the point p and vector v.

reflectAbout :: (Transformable t, V t ~ R2) => P2 -> R2 -> t -> tSource

reflectAbout p v reflects a diagram in the line determined by the point p and the vector v.

Combinators

strutX :: (Backend b R2, Monoid m) => Double -> AnnDiagram b R2 mSource

strutX d is an empty diagram with width d and height 0. Note that strutX (-w) behaves the same as strutX w.

strutY :: (Backend b R2, Monoid m) => Double -> AnnDiagram b R2 mSource

strutY d is an empty diagram with height d and width 0. Note that strutX (-w) behaves the same as strutX w.

(===) :: (HasOrigin a, Boundable a, V a ~ R2, Monoid a) => a -> a -> aSource

Place two diagrams (or other boundable objects) vertically adjacent to one another, with the first diagram above the second. Since Haskell ignores whitespace in expressions, one can thus write

    c
   ===
    d

to place c above d.

(|||) :: (HasOrigin a, Boundable a, V a ~ R2, Monoid a) => a -> a -> aSource

Place two diagrams (or other boundable objects) horizontally adjacent to one another, with the first diagram to the left of the second.

hcat :: (HasOrigin a, Boundable a, Qualifiable a, V a ~ R2, Monoid a) => [a] -> aSource

Lay out a list of boundable objects in a row from left to right, so that their local origins lie along a single horizontal line, with successive bounding regions tangent to one another.

  • For more control over the spacing, see hcat'.
  • To align the diagrams vertically (or otherwise), use alignment combinators (such as alignT or alignB) from Diagrams.TwoD.Align before applying hcat.
  • For non-axis-aligned layout, see cat.

hcat' :: (HasOrigin a, Boundable a, Qualifiable a, V a ~ R2, Monoid a) => CatOpts R2 -> [a] -> aSource

A variant of hcat taking an extra CatOpts record to control the spacing. See the cat' documentation for a description of the possibilities.

vcat :: (HasOrigin a, Boundable a, Qualifiable a, V a ~ R2, Monoid a) => [a] -> aSource

Lay out a list of boundable objects in a column from top to bottom, so that their local origins lie along a single vertical line, with successive bounding regions tangent to one another.

  • For more control over the spacing, see vcat'.
  • To align the diagrams horizontally (or otherwise), use alignment combinators (such as alignL or alignR) from Diagrams.TwoD.Align before applying vcat.
  • For non-axis-aligned layout, see cat.

vcat' :: (HasOrigin a, Boundable a, Qualifiable a, V a ~ R2, Monoid a) => CatOpts R2 -> [a] -> aSource

A variant of vcat taking an extra CatOpts record to control the spacing. See the cat' documentation for a description of the possibilities.

Alignment

alignL :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

Align along the left edge, i.e. translate the diagram in a horizontal direction so that the local origin is on the left edge of the bounding region.

alignR :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

Align along the right edge.

alignT :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

Align along the top edge.

alignB :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

Align along the bottom edge.

alignTL :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

alignTR :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

alignBL :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

alignBR :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

alignX :: (HasOrigin a, Boundable a, V a ~ R2) => Double -> a -> aSource

alignX moves the local origin horizontally as follows:

  • alignX (-1) moves the local origin to the left edge of the bounding region;
  • align 1 moves the local origin to the right edge;
  • any other argument interpolates linearly between these. For example, alignX 0 centers, alignX 2 moves the origin one "radius" to the right of the right edge, and so on.

alignY :: (HasOrigin a, Boundable a, V a ~ R2) => Double -> a -> aSource

Like alignX, but moving the local origin vertically, with an argument of 1 corresponding to the top edge and (-1) corresponding to the bottom edge.

centerX :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

Center the local origin along the X-axis.

centerY :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

Center the local origin along the Y-axis.

centerXY :: (HasOrigin a, Boundable a, V a ~ R2) => a -> aSource

Center along both the X- and Y-axes.

Size

Computing size

width :: (Boundable a, V a ~ R2) => a -> DoubleSource

Compute the width of a diagram.

height :: (Boundable a, V a ~ R2) => a -> DoubleSource

Compute the height of a diagram.

size2D :: (Boundable a, V a ~ R2) => a -> (Double, Double)Source

Compute the width and height of a diagram.

extentX :: (Boundable a, V a ~ R2) => a -> (Double, Double)Source

Compute the absolute x-coordinate range of a diagram in R2, in the form (lo,hi).

extentY :: (Boundable a, V a ~ R2) => a -> (Double, Double)Source

Compute the absolute y-coordinate range of a diagram in R2, in the form (lo,hi).

center2D :: (Boundable a, V a ~ R2) => a -> P2Source

Compute the point at the center (in the x- and y-directions) of a diagram.

Specifying size

data SizeSpec2D Source

A specification of a (requested) rectangular size.

Constructors

Width Double

Specify an explicit width. The height should be determined automatically (so as to preserve aspect ratio).

Height Double

Specify an explicit height. The width should be determined automatically (so as to preserve aspect ratio)

Dims Double Double

An explicit specification of both dimensions.

Absolute

Absolute size: use whatever size an object already has; do not rescale.

Visual aids for understanding the internal model

showOrigin :: (Renderable Ellipse b, Backend b R2, Monoid m) => AnnDiagram b R2 m -> AnnDiagram b R2 mSource

Mark the origin of a diagram by placing a red dot 1/50th its size.