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

Copyright(c) 2011 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

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

data R2 Source

The two-dimensional Euclidean vector space R^2. This type is intentionally abstract.

r2 (3,4) :: R2
3 ^& 4    :: R2

Note that Diagrams.Coordinates is not re-exported by Diagrams.Prelude and must be explicitly imported.

  • To construct the vector from the origin to a point p, use p .-. origin.
  • To convert a vector v into the point obtained by following v from the origin, use origin .+^ v.
  • To convert a vector back into a pair of components, use unv2 or coords (from Diagrams.Coordinates). These are typically used in conjunction with the ViewPatterns extension:
foo (unr2 -> (x,y)) = ...
foo (coords -> x :& y) = ...

r2 :: (Double, Double) -> R2 Source

Construct a 2D vector from a pair of components. See also &.

unr2 :: R2 -> (Double, Double) Source

Convert a 2D vector back into a pair of components. See also coords.

mkR2 :: Double -> Double -> R2 Source

Curried form of r2.

type P2 = Point R2 Source

Points in R^2. This type is intentionally abstract.

p2 (3,4)  :: P2
3 ^& 4    :: P2
  • To construct a point from a vector v, use origin .+^ v.
  • To convert a point p into the vector from the origin to p, use p .-. origin.
  • To convert a point back into a pair of coordinates, use unp2, or coords (from Diagrams.Coordinates). It's common to use these in conjunction with the ViewPatterns extension:
foo (unp2 -> (x,y)) = ...
foo (coords -> x :& y) = ...

p2 :: (Double, Double) -> P2 Source

Construct a 2D point from a pair of coordinates. See also ^&.

unp2 :: P2 -> (Double, Double) Source

Convert a 2D point back into a pair of coordinates. See also coords.

mkP2 :: Double -> Double -> P2 Source

Curried form of p2.

type T2 = Transformation R2 Source

Transformations in R^2.

unitX :: R2 Source

The unit vector in the positive X direction.

unitY :: R2 Source

The unit vector in the positive Y direction.

unit_X :: R2 Source

The unit vector in the negative X direction.

unit_Y :: R2 Source

The unit vector in the negative Y direction.

direction :: R2 -> Angle Source

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.

fromDirection :: Angle -> R2 Source

Convert an angle into a unit vector pointing in that direction.

Angles

tau :: Floating a => a Source

The circle constant, the ratio of a circle's circumference to its radius. Note that pi = tau/2.

For more information and a well-reasoned argument why we should all be using tau instead of pi, see The Tau Manifesto, http://tauday.com/.

To hear what it sounds like (and to easily memorize the first 30 digits or so), try http://youtu.be/3174T-3-59Q.

Paths

Stroking

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

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, IsName a) => StrokeOpts a -> Path R2 -> Diagram b R2 Source

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.

strokeTrail :: Renderable (Path R2) b => Trail R2 -> Diagram b R2 Source

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 strokeTrail as well. The solution is to give a type signature to expressions involving strokeTrail, or (recommended) upgrade GHC (the bug is fixed in 7.0.2 onwards).

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

Deprecated synonym for strokeTrail.

strokeTrail' :: (Renderable (Path R2) b, IsName a) => StrokeOpts a -> Trail R2 -> Diagram b R2 Source

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

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

Deprecated synonym for strokeTrail'.

strokeLine :: Renderable (Path R2) b => Trail' Line R2 -> Diagram b R2 Source

A composition of strokeT and wrapLine for conveniently converting a line directly into a diagram.

strokeLoop :: Renderable (Path R2) b => Trail' Loop R2 -> Diagram b R2 Source

A composition of strokeT and wrapLoop for conveniently converting a loop directly into a diagram.

strokeLocTrail :: Renderable (Path R2) b => Located (Trail R2) -> Diagram b R2 Source

A convenience function for converting a Located Trail directly into a diagram; strokeLocTrail = stroke . trailLike.

strokeLocT :: Renderable (Path R2) b => Located (Trail R2) -> Diagram b R2 Source

Deprecated synonym for strokeLocTrail.

strokeLocLine :: Renderable (Path R2) b => Located (Trail' Line R2) -> Diagram b R2 Source

A convenience function for converting a Located line directly into a diagram; strokeLocLine = stroke . trailLike . mapLoc wrapLine.

strokeLocLoop :: Renderable (Path R2) b => Located (Trail' Loop R2) -> Diagram b R2 Source

A convenience function for converting a Located loop directly into a diagram; strokeLocLoop = stroke . trailLike . mapLoc wrapLoop.

data FillRule Source

Enumeration of algorithms or "rules" for determining which points lie in the interior of a (possibly self-intersecting) closed path.

Constructors

Winding

Interior points are those with a nonzero winding number. See http://en.wikipedia.org/wiki/Nonzero-rule.

EvenOdd

Interior points are those where a ray extended infinitely in a particular direction crosses the path an odd number of times. See http://en.wikipedia.org/wiki/Even-odd_rule.

fillRule :: HasStyle a => FillRule -> a -> a Source

Specify the fill rule that should be used for determining which points are inside a path.

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]]
 
_queryFillRule :: FillRule
 

Instances

vertexNames :: forall a a'. Lens (StrokeOpts a) (StrokeOpts a') [[a]] [[a']] Source

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.

queryFillRule :: forall a. Lens' (StrokeOpts a) FillRule Source

The fill rule used for determining which points are inside the path. The default is Winding. NOTE: for now, this only affects the resulting diagram's Query, not how it will be drawn! To set the fill rule determining how it is to be drawn, use the fillRule function.

Clipping

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

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 envelope of the diagram is unaffected.

clipTo :: Renderable (Path R2) b => Path R2 -> Diagram b R2 -> Diagram b R2 Source

Clip a diagram to the given path setting its envelope to the pointwise minimum of the envelopes of the diagram and path. The trace consists of those parts of the original diagram's trace which fall within the clipping path, or parts of the path's trace within the original diagram.

clipped :: Renderable (Path R2) b => Path R2 -> Diagram b R2 -> Diagram b R2 Source

Clip a diagram to the clip path taking the envelope and trace of the clip path.

Shapes

Rules

hrule :: (TrailLike t, V t ~ R2) => Double -> t Source

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

hruleEx = vcat' (with & sep .~ 0.2) (map hrule [1..5])
        # centerXY # pad 1.1

vrule :: (TrailLike t, V t ~ R2) => Double -> t Source

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

vruleEx = hcat' (with & sep .~ 0.2) (map vrule [1, 1.2 .. 2])
        # centerXY # pad 1.1

Circle-ish things

unitCircle :: (TrailLike t, V t ~ R2) => t Source

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

circle :: (TrailLike t, V t ~ R2, Transformable t) => Double -> t Source

A circle of the given radius, centered at the origin. As a path, it begins at (r,0).

ellipse :: (TrailLike t, V t ~ R2, Transformable t) => Double -> t Source

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 :: (TrailLike t, V t ~ R2, Transformable t) => Double -> Double -> t Source

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 :: (TrailLike t, V t ~ R2) => Angle -> Angle -> t Source

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. The origin of the arc is its center.

arc' :: (TrailLike p, V p ~ R2) => Double -> Angle -> Angle -> p Source

Given a radus r, a start angle s and an end angle e, arc' r s e is the path of a radius (abs r) arc between the two angles. If a negative radius is given, the arc will be clockwise, otherwise it will be counterclockwise. The origin of the arc is its center.

arc'Ex = mconcat [ arc' r (0 @@ turn) (1/4 @@ turn) | r <- [0.5,-1,1.5] ]
       # centerXY # pad 1.1

arcCW :: (TrailLike t, V t ~ R2) => Angle -> Angle -> t Source

Like arc but clockwise.

wedge :: (TrailLike p, V p ~ R2) => Double -> Angle -> Angle -> p Source

Create a circular wedge of the given radius, beginning at the first angle and extending counterclockwise to the second.

wedgeEx = hcat' (with & sep .~ 0.5)
  [ wedge 1 (0 @@ turn) (1/4 @@ turn)
  , wedge 1 (7/30 @@ turn) (11/30 @@ turn)
  , wedge 1 (1/8 @@ turn) (7/8 @@ turn)
  ]
  # fc blue
  # centerXY # pad 1.1

arcBetween :: (TrailLike t, V t ~ R2) => P2 -> P2 -> Double -> t Source

arcBetween p q height creates an arc beginning at p and ending at q, with its midpoint at a distance of abs height away from the straight line from p to q. A positive value of height results in an arc to the left of the line from p to q; a negative value yields one to the right.

arcBetweenEx = mconcat
  [ arcBetween origin (p2 (2,1)) ht | ht <- [-0.2, -0.1 .. 0.2] ]
  # centerXY # pad 1.1

annularWedge :: (TrailLike p, V p ~ R2) => Double -> Double -> Angle -> Angle -> p Source

Create an annular wedge of the given radii, beginning at the first angle and extending counterclockwise to the second. The radius of the outer circle is given first.

annularWedgeEx = hcat' (with & sep .~ 0.50)
  [ annularWedge 1 0.5 (0 @@ turn) (1/4 @@ turn)
  , annularWedge 1 0.3 (7/30 @@ turn) (11/30 @@ turn)
  , annularWedge 1 0.7 (1/8 @@ turn) (7/8 @@ turn)
  ]
  # fc blue
  # centerXY # pad 1.1

General polygons

polygon :: (TrailLike t, V t ~ R2) => PolygonOpts -> t Source

Generate the polygon described by the given options.

polyTrail :: PolygonOpts -> Located (Trail R2) Source

Generate a polygon. See PolygonOpts for more information.

data PolygonOpts Source

Options for specifying a polygon.

Instances

Default PolygonOpts

The default polygon is a regular pentagon of radius 1, centered at the origin, aligned to the x-axis.

polyType :: Lens' PolygonOpts PolyType Source

Specification for the polygon's vertices.

polyOrient :: Lens' PolygonOpts PolyOrientation Source

Should a rotation be applied to the polygon in order to orient it in a particular way?

polyCenter :: Lens' PolygonOpts P2 Source

Should a translation be applied to the polygon in order to place the center at a particular location?

data PolyType Source

Method used to determine the vertices of a polygon.

Constructors

PolyPolar [Angle] [Double]

A "polar" polygon.

  • The first argument is a list of central angles from each vertex to the next.
  • The second argument is a list of radii from the origin to each successive vertex.

To construct an n-gon, use a list of n-1 angles and n radii. Extra angles or radii are ignored.

Cyclic polygons (with all vertices lying on a circle) can be constructed using a second argument of (repeat r).

PolySides [Angle] [Double]

A polygon determined by the distance between successive vertices and the angles formed by each three successive vertices. In other words, a polygon specified by "turtle graphics": go straight ahead x1 units; turn by angle a1; go straght ahead x2 units; turn by angle a2; etc. The polygon will be centered at the centroid of its vertices.

  • The first argument is a list of vertex angles, giving the angle at each vertex from the previous vertex to the next. The first angle in the list is the angle at the second vertex; the first edge always starts out heading in the positive y direction from the first vertex.
  • The second argument is a list of distances between successive vertices.

To construct an n-gon, use a list of n-2 angles and n-1 edge lengths. Extra angles or lengths are ignored.

PolyRegular Int Double

A regular polygon with the given number of sides (first argument) and the given radius (second argument).

data PolyOrientation Source

Determine how a polygon should be oriented.

Constructors

NoOrient

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

OrientH

Orient horizontally, so the bottommost edge is parallel to the x-axis.

OrientV

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

OrientTo R2

Orient so some edge is facing in the direction of, that is, perpendicular to, the given vector.

Star polygons

data StarOpts Source

Options for creating "star" polygons, where the edges connect possibly non-adjacent vertices.

Constructors

StarFun (Int -> Int)

Specify the order in which the vertices should be connected by a function that maps each vertex index to the index of the vertex that should come next. Indexing of vertices begins at 0.

StarSkip Int

Specify a star polygon by a "skip". A skip of 1 indicates a normal polygon, where edges go between successive vertices. A skip of 2 means that edges will connect every second vertex, skipping one in between. Generally, a skip of n means that edges will connect every nth vertex.

star :: StarOpts -> [P2] -> Path R2 Source

Create a generalized star polygon. The StarOpts are used to determine in which order the given vertices should be connected. The intention is that the second argument of type [P2] could be generated by a call to polygon, regPoly, or the like, since a list of vertices is TrailLike. But of course the list can be generated any way you like. A Path R2 is returned (instead of any TrailLike) because the resulting path may have more than one component, for example if the vertices are to be connected in several disjoint cycles.

Regular polygons

regPoly :: (TrailLike t, V t ~ R2) => Int -> Double -> t Source

Create a regular polygon. The first argument is the number of sides, and the second is the length of the sides. (Compare to the polygon function with a PolyRegular option, which produces polygons of a given radius).

The polygon will be oriented with one edge parallel to the x-axis.

triangle :: (TrailLike t, V t ~ R2) => Double -> t Source

An equilateral triangle, with sides of the given length and base parallel to the x-axis.

eqTriangle :: (TrailLike t, V t ~ R2) => Double -> t Source

A synonym for triangle, provided for backwards compatibility.

square :: (TrailLike t, Transformable t, V t ~ R2) => Double -> t Source

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

pentagon :: (TrailLike t, V t ~ R2) => Double -> t Source

A regular pentagon, with sides of the given length and base parallel to the x-axis.

hexagon :: (TrailLike t, V t ~ R2) => Double -> t Source

A regular hexagon, with sides of the given length and base parallel to the x-axis.

heptagon :: (TrailLike t, V t ~ R2) => Double -> t Source

A regular heptagon, with sides of the given length and base parallel to the x-axis.

septagon :: (TrailLike t, V t ~ R2) => Double -> t Source

A synonym for heptagon. It is, however, completely inferior, being a base admixture of the Latin septum (seven) and the Greek γωνία (angle).

octagon :: (TrailLike t, V t ~ R2) => Double -> t Source

A regular octagon, with sides of the given length and base parallel to the x-axis.

nonagon :: (TrailLike t, V t ~ R2) => Double -> t Source

A regular nonagon, with sides of the given length and base parallel to the x-axis.

decagon :: (TrailLike t, V t ~ R2) => Double -> t Source

A regular decagon, with sides of the given length and base parallel to the x-axis.

hendecagon :: (TrailLike t, V t ~ R2) => Double -> t Source

A regular hendecagon, with sides of the given length and base parallel to the x-axis.

dodecagon :: (TrailLike t, V t ~ R2) => Double -> t Source

A regular dodecagon, with sides of the given length and base parallel to the x-axis.

Other special polygons

unitSquare :: (TrailLike t, V t ~ R2) => t Source

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

rect :: (TrailLike t, Transformable t, V t ~ R2) => Double -> Double -> t Source

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

Other shapes

roundedRect :: (TrailLike t, V t ~ R2) => Double -> Double -> Double -> t Source

roundedRect w h r generates a closed trail, or closed path centered at the origin, of an axis-aligned rectangle with width w, height h, and circular rounded corners of radius r. If r is negative the corner will be cut out in a reverse arc. If the size of r is larger than half the smaller dimension of w and h, then it will be reduced to fit in that range, to prevent the corners from overlapping. The trail or path begins with the right edge and proceeds counterclockwise. If you need to specify a different radius for each corner individually, use roundedRect' instead.

roundedRectEx = pad 1.1 . centerXY $ hcat' (with & sep .~ 0.2)
  [ roundedRect  0.5 0.4 0.1
  , roundedRect  0.5 0.4 (-0.1)
  , roundedRect' 0.7 0.4 (with & radiusTL .~ 0.2
                               & radiusTR .~ -0.2
                               & radiusBR .~ 0.1)
  ]

roundedRect' :: (TrailLike t, V t ~ R2) => Double -> Double -> RoundedRectOpts -> t Source

roundedRect' works like roundedRect but allows you to set the radius of each corner indivually, using RoundedRectOpts. The default corner radius is 0. Each radius can also be negative, which results in the curves being reversed to be inward instead of outward.

Arrows

arrowV :: Renderable (Path R2) b => R2 -> Diagram b R2 Source

arrowV v creates an arrow with the direction and magnitude of the vector v (with its tail at the origin), using default parameters.

arrowV' :: Renderable (Path R2) b => ArrowOpts -> R2 -> Diagram b R2 Source

arrowV' v creates an arrow with the direction and magnitude of the vector v (with its tail at the origin).

arrowAt :: Renderable (Path R2) b => P2 -> R2 -> Diagram b R2 Source

Create an arrow starting at s with length and direction determined by the vector v.

arrowBetween :: Renderable (Path R2) b => P2 -> P2 -> Diagram b R2 Source

arrowBetween s e creates an arrow pointing from s to e with default parameters.

arrowBetween' :: Renderable (Path R2) b => ArrowOpts -> P2 -> P2 -> Diagram b R2 Source

arrowBetween' opts s e creates an arrow pointing from s to e using the given options. In particular, it scales and rotates arrowShaft to go between s and e, taking head, tail, and gaps into account.

connect :: (Renderable (Path R2) b, IsName n1, IsName n2) => n1 -> n2 -> Diagram b R2 -> Diagram b R2 Source

Connect two diagrams with a straight arrow.

connect' :: (Renderable (Path R2) b, IsName n1, IsName n2) => ArrowOpts -> n1 -> n2 -> Diagram b R2 -> Diagram b R2 Source

Connect two diagrams with an arbitrary arrow.

connectPerim :: (Renderable (Path R2) b, IsName n1, IsName n2) => n1 -> n2 -> Angle -> Angle -> Diagram b R2 -> Diagram b R2 Source

Connect two diagrams at point on the perimeter of the diagrams, choosen by angle.

connectPerim' :: (Renderable (Path R2) b, IsName n1, IsName n2) => ArrowOpts -> n1 -> n2 -> Angle -> Angle -> Diagram b R2 -> Diagram b R2 Source

connectOutside :: (Renderable (Path R2) b, IsName n1, IsName n2) => n1 -> n2 -> Diagram b R2 -> Diagram b R2 Source

Draw an arrow from diagram named "n1" to diagram named "n2". The arrow lies on the line between the centres of the diagrams, but is drawn so that it stops at the boundaries of the diagrams, using traces to find the intersection points.

connectOutside' :: (Renderable (Path R2) b, IsName n1, IsName n2) => ArrowOpts -> n1 -> n2 -> Diagram b R2 -> Diagram b R2 Source

arrow :: Renderable (Path R2) b => Double -> Diagram b R2 Source

arrow len creates an arrow of length len with default parameters, starting at the origin and ending at the point (len,0).

arrow' :: Renderable (Path R2) b => ArrowOpts -> Double -> Diagram b R2 Source

arrow' opts len creates an arrow of length len using the given options, starting at the origin and ending at the point (len,0). In particular, it scales the given arrowShaft so that the entire arrow has length len.

straightShaft :: Trail R2 Source

Straight line arrow shaft.

arrowHead :: Lens' ArrowOpts ArrowHT Source

A shape to place at the head of the arrow.

arrowTail :: Lens' ArrowOpts ArrowHT Source

A shape to place at the tail of the arrow.

arrowShaft :: Lens' ArrowOpts (Trail R2) Source

The trail to use for the arrow shaft.

headGap :: Lens' ArrowOpts (Measure R2) Source

Distance to leave between the head and the target point.

tailGap :: Lens' ArrowOpts (Measure R2) Source

Distance to leave between the starting point and the tail.

gaps :: Traversal' ArrowOpts (Measure R2) Source

Set both the headGap and tailGap simultaneously.

gap :: Traversal' ArrowOpts (Measure R2) Source

Same as gaps, provided for backward compatiiblity.

headTexture :: Setter' ArrowOpts Texture Source

A lens for setting or modifying the texture of an arrowhead. For example, one may write ... (with & headTexture .~ grad) to get an arrow with a head filled with a gradient, assuming grad has been defined. Or ... (with & headTexture .~ solid blue to set the head color to blue. For more general control over the style of arrowheads, see headStyle.

headStyle :: Lens' ArrowOpts (Style R2) Source

Style to apply to the head. headStyle is modified by using the lens combinator %~ to change the current style. For example, to change an opaque black arrowhead to translucent orange: (with & headStyle %~ fc orange . opacity 0.75).

tailTexture :: Setter' ArrowOpts Texture Source

A lens for setting or modifying the texture of an arrow tail.

tailStyle :: Lens' ArrowOpts (Style R2) Source

Style to apply to the tail. See headStyle.

shaftTexture :: Setter' ArrowOpts Texture Source

A lens for setting or modifying the texture of an arrow shaft.

shaftStyle :: Lens' ArrowOpts (Style R2) Source

Style to apply to the shaft. See headStyle.

headLength :: Lens' ArrowOpts (Measure R2) Source

The length from the start of the joint to the tip of the head.

tailLength :: Lens' ArrowOpts (Measure R2) Source

The length of the tail plus its joint.

lengths :: Traversal' ArrowOpts (Measure R2) Source

Set both the headLength and tailLength simultaneously.

Text

text :: Renderable Text b => String -> Diagram b R2 Source

Create a primitive text diagram from the given string, with center alignment, equivalent to alignedText 0.5 0.5.

Note that it takes up no space, as text size information is not available.

topLeftText :: Renderable Text b => String -> Diagram b R2 Source

Create a primitive text diagram from the given string, origin at the top left corner of the text's bounding box, equivalent to alignedText 0 1.

Note that it takes up no space.

alignedText :: Renderable Text b => Double -> Double -> String -> Diagram b R2 Source

Create a primitive text diagram from the given string, with the origin set to a point interpolated within the bounding box. The first parameter varies from 0 (left) to 1 (right), and the second parameter from 0 (bottom) to 1 (top).

The height of this box is determined by the font's potential ascent and descent, rather than the height of the particular string.

Note that it takes up no space.

baselineText :: Renderable Text b => String -> Diagram b R2 Source

Create a primitive text diagram from the given string, with the origin set to be on the baseline, at the beginning (although not bounding). This is the reference point of showText in the Cairo graphics library.

Note that it takes up no space.

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

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

italic :: HasStyle a => a -> a Source

Set all text in italics.

oblique :: HasStyle a => a -> a Source

Set all text using an oblique slant.

bold :: HasStyle a => a -> a Source

Set all text using a bold font weight.

fontSize :: (HasStyle a, V a ~ R2) => Measure R2 -> a -> a Source

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.

fontSizeO :: (HasStyle a, V a ~ R2) => Double -> a -> a Source

A convenient synonym for 'fontSize (Output w)'.

fontSizeL :: (HasStyle a, V a ~ R2) => Double -> a -> a Source

A convenient sysnonym for 'fontSize (Local w)'.

fontSizeN :: (HasStyle a, V a ~ R2) => Double -> a -> a Source

A convenient synonym for 'fontSize (Normalized w)'.

fontSizeG :: (HasStyle a, V a ~ R2) => Double -> a -> a Source

A convenient synonym for 'fontSize (Global w)'.

Images

data DImage :: * -> * where Source

An image primitive, the two ints are width followed by height. Will typically be created by loadImageEmb or loadImageExt which, will handle setting the width and heigh to the actual width and height of the image.

Constructors

DImage :: ImageData t -> Int -> Int -> T2 -> DImage t 

Instances

data ImageData :: * -> * where Source

ImageData is either a JuicyPixels DynamicImage tagged as Embedded or a reference tagged as External.

data Embedded Source

Instances

data External Source

Instances

image :: (Typeable a, Renderable (DImage a) b) => DImage a -> Diagram b R2 Source

Make a DImage into a Diagram.

loadImageEmb :: FilePath -> IO (Either String (DImage Embedded)) Source

Use JuicyPixels to read an image in any format and wrap it in a DImage. The width and height of the image are set to their actual values.

loadImageExt :: FilePath -> IO (Either String (DImage External)) Source

Check that a file exists, and use JuicyPixels to figure out the right size, but save a reference to the image instead of the raster data

uncheckedImageRef :: FilePath -> Int -> Int -> DImage External Source

Make an "unchecked" image reference; have to specify a width and height. Unless the aspect ratio of the external image is the w :: h, then the image will be distorted.

raster :: (Int -> Int -> AlphaColour Double) -> Int -> Int -> DImage Embedded Source

Create an image "from scratch" by specifying the pixel data

rasterDia :: Renderable (DImage Embedded) b => (Int -> Int -> AlphaColour Double) -> Int -> Int -> Diagram b R2 Source

Crate a diagram from raw raster data.

Transformations

Rotation

rotation :: Angle -> T2 Source

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

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

Rotate about the local origin by the given angle. Positive angles correspond to counterclockwise rotation, negative to clockwise. The angle can be expressed using any of the Isos on Angle. For example, rotate (1/4 @@ turn), rotate (tau/4 @@ rad), and rotate (90 @@ deg) all represent the same transformation, namely, a counterclockwise rotation by a right angle. To rotate about some point other than the local origin, see rotateAbout.

Note that writing rotate (1/4), with no Angle constructor, 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 interprets its argument as a number of turns.

rotateBy :: (Transformable t, V t ~ R2) => Double -> t -> t Source

A synonym for rotate, interpreting its argument in units of turns; it can be more convenient to write rotateBy (1/4) than rotate (1/4 @@ turn).

rotationAbout :: P2 -> Angle -> T2 Source

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

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

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

Scaling

scalingX :: Double -> T2 Source

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

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

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

scalingY :: Double -> T2 Source

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

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

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

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

Create a uniform scaling transformation.

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

Scale uniformly in every dimension by the given scalar.

scaleToX :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> t Source

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 :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> t Source

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 height of 0, such as hrule.

scaleUToX :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> t Source

scaleUToX w scales a diagram uniformly by whatever factor required to make its width w. scaleUToX should not be applied to diagrams with a width of 0, such as vrule.

scaleUToY :: (Enveloped t, Transformable t, V t ~ R2) => Double -> t -> t Source

scaleUToY h scales a diagram uniformly by whatever factor required to make its height h. scaleUToY should not be applied to diagrams with a height of 0, such as hrule.

Translation

translationX :: Double -> T2 Source

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

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

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

translationY :: Double -> T2 Source

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

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

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 :: T2 Source

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 -> t Source

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

reflectionY :: T2 Source

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 -> t Source

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

reflectionAbout :: P2 -> R2 -> T2 Source

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 -> t Source

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

Shears

shearingX :: Double -> T2 Source

shearingX d is the linear transformation which is the identity on y coordinates and sends (0,1) to (d,1).

shearX :: (Transformable t, V t ~ R2) => Double -> t -> t Source

shearX d performs a shear in the x-direction which sends (0,1) to (d,1).

shearingY :: Double -> T2 Source

shearingY d is the linear transformation which is the identity on x coordinates and sends (1,0) to (1,d).

shearY :: (Transformable t, V t ~ R2) => Double -> t -> t Source

shearY d performs a shear in the y-direction which sends (1,0) to (1,d).

Deformations - non-affine transforms

parallelX0 :: Deformation R2 Source

The parallel projection onto the line x=0

perspectiveX1 :: Deformation R2 Source

The perspective division onto the line x=1 along lines going through the origin.

parallelY0 :: Deformation R2 Source

The parallel projection onto the line y=0

perspectiveY1 :: Deformation R2 Source

The perspective division onto the line y=1 along lines going through the origin.

facingX :: Deformation R2 Source

The viewing transform for a viewer facing along the positive X axis. X coördinates stay fixed, while Y coördinates are compressed with increasing distance. asDeformation (translation unitX) <> parallelX0 <> frustrumX = perspectiveX1

Combinators

Combining multiple diagrams

(===) :: (Juxtaposable a, V a ~ R2, Semigroup a) => a -> a -> a infixl 6 Source

Place two diagrams (or other 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. The local origin of the resulting combined diagram is the same as the local origin of the first. (===) is associative and has mempty as an identity. See the documentation of beside for more information.

(|||) :: (Juxtaposable a, V a ~ R2, Semigroup a) => a -> a -> a infixl 6 Source

Place two diagrams (or other juxtaposable objects) horizontally adjacent to one another, with the first diagram to the left of the second. The local origin of the resulting combined diagram is the same as the local origin of the first. (|||) is associative and has mempty as an identity. See the documentation of beside for more information.

atAngle :: (Juxtaposable a, V a ~ R2, Semigroup a) => Angle -> a -> a -> a Source

Place two diagrams (or other juxtaposable objects) adjacent to one another, with the second diagram placed along a line at angle th from the first. The local origin of the resulting combined diagram is the same as the local origin of the first. See the documentation of beside for more information.

hcat :: (Juxtaposable a, HasOrigin a, Monoid' a, V a ~ R2) => [a] -> a Source

Lay out a list of juxtaposable objects in a row from left to right, so that their local origins lie along a single horizontal line, with successive envelopes 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' :: (Juxtaposable a, HasOrigin a, Monoid' a, V a ~ R2) => CatOpts R2 -> [a] -> a Source

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

vcat :: (Juxtaposable a, HasOrigin a, Monoid' a, V a ~ R2) => [a] -> a Source

Lay out a list of juxtaposable objects in a column from top to bottom, so that their local origins lie along a single vertical line, with successive envelopes 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' :: (Juxtaposable a, HasOrigin a, Monoid' a, V a ~ R2) => CatOpts R2 -> [a] -> a Source

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

Spacing and envelopes

strutX :: (Backend b R2, Monoid' m) => Double -> QDiagram b R2 m Source

strutX w is an empty diagram with width w, height 0, and a centered local origin. Note that strutX (-w) behaves the same as strutX w.

strutY :: (Backend b R2, Monoid' m) => Double -> QDiagram b R2 m Source

strutY h is an empty diagram with height h, width 0, and a centered local origin. Note that strutY (-h) behaves the same as strutY h.

padX :: (Backend b R2, Monoid' m) => Double -> QDiagram b R2 m -> QDiagram b R2 m Source

padX s "pads" a diagram in the x-direction, expanding its envelope horizontally by a factor of s (factors between 0 and 1 can be used to shrink the envelope). Note that the envelope will expand with respect to the local origin, so if the origin is not centered horizontally the padding may appear "uneven". If this is not desired, the origin can be centered (using centerX) before applying padX.

padY :: (Backend b R2, Monoid' m) => Double -> QDiagram b R2 m -> QDiagram b R2 m Source

padY s "pads" a diagram in the y-direction, expanding its envelope vertically by a factor of s (factors between 0 and 1 can be used to shrink the envelope). Note that the envelope will expand with respect to the local origin, so if the origin is not centered vertically the padding may appear "uneven". If this is not desired, the origin can be centered (using centerY) before applying padY.

extrudeLeft :: Monoid' m => Double -> QDiagram b R2 m -> QDiagram b R2 m Source

extrudeLeft s "extrudes" a diagram in the negative x-direction, offsetting its envelope by the provided distance. When s < 0 , the envelope is inset instead.

See the documentation for extrudeEnvelope for more information.

extrudeRight :: Monoid' m => Double -> QDiagram b R2 m -> QDiagram b R2 m Source

extrudeRight s "extrudes" a diagram in the positive x-direction, offsetting its envelope by the provided distance. When s < 0 , the envelope is inset instead.

See the documentation for extrudeEnvelope for more information.

extrudeBottom :: Monoid' m => Double -> QDiagram b R2 m -> QDiagram b R2 m Source

extrudeBottom s "extrudes" a diagram in the negative y-direction, offsetting its envelope by the provided distance. When s < 0 , the envelope is inset instead.

See the documentation for extrudeEnvelope for more information.

extrudeTop :: Monoid' m => Double -> QDiagram b R2 m -> QDiagram b R2 m Source

extrudeTop s "extrudes" a diagram in the positive y-direction, offsetting its envelope by the provided distance. When s < 0 , the envelope is inset instead.

See the documentation for extrudeEnvelope for more information.

view :: (Backend b R2, Monoid' m) => P2 -> R2 -> QDiagram b R2 m -> QDiagram b R2 m Source

view p v sets the envelope of a diagram to a rectangle whose lower-left corner is at p and whose upper-right corner is at p .+^ v. Useful for selecting the rectangular portion of a diagram which should actually be "viewed" in the final render, if you don't want to see the entire diagram.

Background

boundingRect :: (Enveloped t, Transformable t, TrailLike t, Monoid t, V t ~ R2, Enveloped a, V a ~ R2) => a -> t Source

Construct a bounding rectangle for an enveloped object, that is, the smallest axis-aligned rectangle which encloses the object.

bg :: Renderable (Path R2) b => Colour Double -> Diagram b R2 -> Diagram b R2 Source

"Set the background color" of a diagram. That is, place a diagram atop a bounding rectangle of the given color.

Alignment

alignL :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

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

alignR :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

Align along the right edge.

alignT :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

Align along the top edge.

alignB :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

Align along the bottom edge.

alignTL :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

alignTR :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

alignBL :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

alignBR :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

alignX :: (Alignable a, HasOrigin a, V a ~ R2) => Double -> a -> a Source

alignX and snugX move the local origin horizontally as follows:

  • alignX (-1) moves the local origin to the left edge of the boundary;
  • 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.
  • snugX works the same way.

alignY :: (Alignable a, HasOrigin a, V a ~ R2) => Double -> a -> a Source

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 :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

Center the local origin along the X-axis.

centerY :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

Center the local origin along the Y-axis.

centerXY :: (Alignable a, HasOrigin a, V a ~ R2) => a -> a Source

Center along both the X- and Y-axes.

Snugging

snugL :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugR :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugT :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugB :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugTL :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugTR :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugBL :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugBR :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugX :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => Double -> a -> a Source

See the documentation for alignX.

snugY :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => Double -> a -> a Source

snugCenterX :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugCenterY :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

snugCenterXY :: (Fractional (Scalar (V a)), Alignable a, Traced a, HasOrigin a, V a ~ R2) => a -> a Source

Size

Computing size

width :: (Enveloped a, V a ~ R2) => a -> Double Source

Compute the width of an enveloped object.

height :: (Enveloped a, V a ~ R2) => a -> Double Source

Compute the height of an enveloped object.

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

Compute the width and height of an enveloped object.

sizeSpec2D :: (Enveloped a, V a ~ R2) => a -> SizeSpec2D Source

Compute the size of an enveloped object as a SizeSpec2D value.

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

Compute the absolute x-coordinate range of an enveloped object in R2, in the form (lo,hi). Return Nothing for objects with an empty envelope.

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

Compute the absolute y-coordinate range of an enveloped object in R2, in the form (lo,hi).

center2D :: (Enveloped a, V a ~ R2) => a -> P2 Source

Compute the point at the center (in the x- and y-directions) of a enveloped object. Return the origin for objects with an empty envelope.

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 a width and height.

Absolute

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

mkSizeSpec :: Maybe Double -> Maybe Double -> SizeSpec2D Source

Create a size specification from a possibly-specified width and height.

Adjusting size

sized :: (Transformable a, Enveloped a, V a ~ R2) => SizeSpec2D -> a -> a Source

Uniformly scale any enveloped object so that it fits within the given size.

sizedAs :: (Transformable a, Enveloped a, V a ~ R2, Enveloped b, V b ~ R2) => b -> a -> a Source

Uniformly scale an enveloped object so that it "has the same size as" (fits within the width and height of) some other object.

Textures

data Texture Source

A Texture is either a color SC, linear gradient LG, or radial gradient RG. An object can have only one texture which is determined by the Last semigroup structure.

Instances

solid :: Color a => a -> Texture Source

Convert a solid colour into a texture.

data SpreadMethod Source

The SpreadMethod determines what happens before lGradStart and after lGradEnd. GradPad fills the space before the start of the gradient with the color of the first stop and the color after end of the gradient with the color of the last stop. GradRepeat restarts the gradient and GradReflect restarts the gradient with the stops in reverse order.

data GradientStop Source

A gradient stop contains a color and fraction (usually between 0 and 1)

mkStops :: [(Colour Double, Double, Double)] -> [GradientStop] Source

A convenient function for making gradient stops from a list of triples. (An opaque color, a stop fraction, an opacity).

fillTexture :: (HasStyle a, V a ~ R2) => Texture -> a -> a Source

lineTexture :: (HasStyle a, V a ~ R2) => Texture -> a -> a Source

lineTextureA :: (HasStyle a, V a ~ R2) => LineTexture -> a -> a Source

stopFraction :: Lens' GradientStop Double Source

The fraction for stop.

stopColor :: Lens' GradientStop SomeColor Source

A color for the stop.

lGradStops :: Lens' LGradient [GradientStop] Source

A list of stops (colors and fractions).

lGradTrans :: Lens' LGradient T2 Source

A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.

lGradStart :: Lens' LGradient P2 Source

The starting point for the first gradient stop. The coordinates are in Local units and the default is (-0.5, 0).

lGradEnd :: Lens' LGradient P2 Source

The ending point for the last gradient stop.The coordinates are in Local units and the default is (0.5, 0).

lGradSpreadMethod :: Lens' LGradient SpreadMethod Source

For setting the spread method.

defaultLG :: Texture Source

A default is provided so that linear gradients can easily be created using lenses. For example, lg = defaultLG & lGradStart .~ (0.25 ^& 0.33). Note that no default value is provided for lGradStops, this must be set before the gradient value is used, otherwise the object will appear transparent.

mkLinearGradient :: [GradientStop] -> P2 -> P2 -> SpreadMethod -> Texture Source

Make a linear gradient texture from a stop list, start point, end point, and SpreadMethod. The lGradTrans field is set to the identity transfrom, to change it use the lGradTrans lens.

rGradStops :: Lens' RGradient [GradientStop] Source

A list of stops (colors and fractions).

rGradCenter0 :: Lens' RGradient P2 Source

The center point of the inner circle.

rGradRadius0 :: Lens' RGradient Double Source

The radius of the inner cirlce in Local coordinates.

rGradCenter1 :: Lens' RGradient P2 Source

The center of the outer circle.

rGradRadius1 :: Lens' RGradient Double Source

The radius of the outer circle in Local coordinates.

rGradTrans :: Lens' RGradient T2 Source

A transformation to be applied to the gradient. Usually this field will start as the identity transform and capture the transforms that are applied to the gradient.

rGradSpreadMethod :: Lens' RGradient SpreadMethod Source

For setting the spread method.

defaultRG :: Texture Source

A default is provided so that radial gradients can easily be created using lenses. For example, rg = defaultRG & rGradRadius1 .~ 0.25. Note that no default value is provided for rGradStops, this must be set before the gradient value is used, otherwise the object will appear transparent.

mkRadialGradient :: [GradientStop] -> P2 -> Double -> P2 -> Double -> SpreadMethod -> Texture Source

Make a radial gradient texture from a stop list, radius, start point, end point, and SpreadMethod. The rGradTrans field is set to the identity transfrom, to change it use the rGradTrans lens.

Colors

fillColor :: (Color c, HasStyle a, V a ~ R2) => c -> a -> a Source

Set the fill color. This function is polymorphic in the color type (so it can be used with either Colour or AlphaColour), but this can sometimes create problems for type inference, so the fc and fcA variants are provided with more concrete types.

fc :: (HasStyle a, V a ~ R2) => Colour Double -> a -> a Source

A synonym for fillColor, specialized to Colour Double (i.e. opaque colors). See comment after fillColor about backends.

fcA :: (HasStyle a, V a ~ R2) => AlphaColour Double -> a -> a Source

A synonym for fillColor, specialized to AlphaColour Double (i.e. colors with transparency). See comment after fillColor about backends.

recommendFillColor :: (Color c, HasStyle a, V a ~ R2) => c -> a -> a Source

Set a "recommended" fill color, to be used only if no explicit calls to fillColor (or fc, or fcA) are used. See comment after fillColor about backends.

lineColor :: (Color c, HasStyle a, V a ~ R2) => c -> a -> a Source

Set the line (stroke) color. This function is polymorphic in the color type (so it can be used with either Colour or AlphaColour), but this can sometimes create problems for type inference, so the lc and lcA variants are provided with more concrete types.

lc :: (HasStyle a, V a ~ R2) => Colour Double -> a -> a Source

A synonym for lineColor, specialized to Colour Double (i.e. opaque colors). See comment in lineColor about backends.

lcA :: (HasStyle a, V a ~ R2) => AlphaColour Double -> a -> a Source

A synonym for lineColor, specialized to AlphaColour Double (i.e. colors with transparency). See comment in lineColor about backends.

Width

data LineWidth Source

Line widths specified on child nodes always override line widths specified at parent nodes.

lineWidth :: (HasStyle a, V a ~ R2) => Measure R2 -> a -> a Source

Set the line (stroke) width.

lineWidthA :: (HasStyle a, V a ~ R2) => LineWidth -> a -> a Source

Apply a LineWidth attribute.

lw :: (HasStyle a, V a ~ R2) => Measure R2 -> a -> a Source

Default for lineWidth.

lwN :: (HasStyle a, V a ~ R2) => Double -> a -> a Source

A convenient synonym for 'lineWidth (Normalized w)'.

lwO :: (HasStyle a, V a ~ R2) => Double -> a -> a Source

A convenient synonym for 'lineWidth (Output w)'.

lwL :: (HasStyle a, V a ~ R2) => Double -> a -> a Source

A convenient sysnonym for 'lineWidth (Local w)'.

lwG :: (HasStyle a, V a ~ R2) => Double -> a -> a Source

A convenient synonym for 'lineWidth (Global w)'.

ultraThin :: Measure R2 Source

Standard Measures.

veryThin :: Measure R2 Source

Standard Measures.

thin :: Measure R2 Source

Standard Measures.

medium :: Measure R2 Source

Standard Measures.

thick :: Measure R2 Source

Standard Measures.

veryThick :: Measure R2 Source

Standard Measures.

ultraThick :: Measure R2 Source

Standard Measures.

none :: Measure R2 Source

Standard Measures.

tiny :: Measure R2 Source

Standard Measures.

verySmall :: Measure R2 Source

Standard Measures.

small :: Measure R2 Source

Standard Measures.

normal :: Measure R2 Source

Standard Measures.

large :: Measure R2 Source

Standard Measures.

veryLarge :: Measure R2 Source

Standard Measures.

huge :: Measure R2 Source

Standard Measures.

Dashing

data Dashing Source

Create lines that are dashing... er, dashed.

Constructors

Dashing [Measure R2] (Measure R2) 

dashing Source

Arguments

:: (HasStyle a, V a ~ R2) 
=> [Measure R2]

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

-> Measure R2

An offset into the dash pattern at which the stroke should start.

-> a 
-> a 

Set the line dashing style.

dashingO :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> a Source

A convenient synonym for 'dashing (Output w)'.

dashingL :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> a Source

A convenient sysnonym for 'dashing (Local w)'.

dashingN :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> a Source

A convenient synonym for 'dashing (Normalized w)'.

dashingG :: (HasStyle a, V a ~ R2) => [Double] -> Double -> a -> a Source

A convenient synonym for 'dashing (Global w)'.

Visual aids for understanding the internal model

showOrigin :: (Renderable (Path R2) b, Backend b R2, Monoid' m) => QDiagram b R2 m -> QDiagram b R2 m Source

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

showOrigin' :: (Renderable (Path R2) b, Backend b R2, Monoid' m) => OriginOpts -> QDiagram b R2 m -> QDiagram b R2 m Source

Mark the origin of a diagram, with control over colour and scale of marker dot.