diagrams-lib-0.1: 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 Angle = DoubleSource

Type synonym used to represent angles in radians.

unitX :: R2Source

A unit vector in the positive X direction.

unitY :: R2Source

A unit vector in the positive Y direction.

Paths

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.

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).

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).

Shapes

Rules

hrule :: (Backend b R2, Renderable (Path R2) b) => Double -> Diagram b R2Source

Create a centered horizontal line of the given length.

vrule :: (Backend b R2, Renderable (Path R2) b) => Double -> Diagram b R2Source

Create a centered vertical line of the given length.

Circle-ish things

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

A circle of radius 1.

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).

arc :: Angle -> Angle -> Path R2Source

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

General polygons

polygon :: (Backend b R2, Renderable (Path R2) b) => PolygonOpts -> Diagram b R2Source

Create a regular polygon from the given options.

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

Create a closed regular polygonal path 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

square :: (Backend b R2, Renderable (Path R2) b) => Diagram b R2Source

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

starPolygon :: (Backend b R2, Renderable (Path R2) b) => Int -> Int -> Diagram b R2Source

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

eqTriangle :: (Backend b R2, Renderable (Path R2) b) => Diagram b R2Source

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

Transformations

Rotation

rotation :: Angle -> Transformation R2Source

Create a transformation which performs a rotation by the given angle in radians.

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

Rotate by the given angle in radians.

rotationBy :: Double -> Transformation R2Source

Create a transformation which performs a rotation by the given fraction of a circle. For example, rotationBy (1/4) rotates by one quarter of a circle (i.e. 90 degrees, i.e. pi/2 radians).

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

Rotate by the given fraction of a circle.

Scaling

scalingX :: Double -> Transformation R2Source

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 -> Transformation R2Source

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.

Translation

translationX :: Double -> Transformation R2Source

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 -> Transformation R2Source

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 :: Transformation R2Source

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 :: Transformation R2Source

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).

Combinators

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

strutX d is an empty diagram with width d and height 0.

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

strutY d is an empty diagram with height d and width 0.

(===) :: (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 alignTop or alignBottom) 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 alignLeft or alignRight) 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) => Rational -> 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) => Rational -> 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.

Utilities

width :: AnnDiagram b R2 m -> DoubleSource

Compute the width of a diagram.

height :: AnnDiagram b R2 m -> DoubleSource

Compute the height of a diagram.

size2D :: AnnDiagram b R2 m -> (Double, Double)Source

Compute the width and height of a diagram.

extentX :: AnnDiagram b R2 a -> (Double, Double)Source

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

extentY :: AnnDiagram b R2 a -> (Double, Double)Source

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

center2D :: AnnDiagram b R2 a -> P2Source

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

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.