| Maintainer | diagrams-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:
- Diagrams.TwoD.Types defines basic types for two-dimensional diagrams, including types representing the 2D Euclidean vector space and various systems of angle measurement.
- Diagrams.TwoD.Align defines alignment combinators specialized to two dimensions (see Diagrams.Align for more general alignment).
- Diagrams.TwoD.Combinators defines ways of combining diagrams specialized to two dimensions (see also Diagrams.Combinators for more general combining).
- Diagrams.TwoD.Transform defines R^2-specific transformations such as rotation by an angle, and scaling, translation, and reflection in the X and Y directions.
- Diagrams.TwoD.Ellipse defines circles and ellipses.
- Diagrams.TwoD.Arc defines circular arcs.
- Diagrams.TwoD.Path exports various operations on two-dimensional paths when viewed as regions of the plane.
- Diagrams.TwoD.Polygons defines general algorithms for drawing various types of polygons.
- Diagrams.TwoD.Shapes defines other two-dimensional shapes, e.g. various polygons.
- Diagrams.TwoD.Text defines primitive text diagrams.
- Diagrams.TwoD.Image allows importing external images into diagrams.
- Diagrams.TwoD.Vector defines some special 2D vectors and functions for converting between vectors and angles.
- Diagrams.TwoD.Size defines functions for working with the size of 2D objects.
- Diagrams.TwoD.Model defines some aids for visualizing diagrams' internal model (local origins, bounding regions, etc.)
- type R2 = (Double, Double)
- type P2 = Point R2
- type T2 = Transformation R2
- unitX :: R2
- unitY :: R2
- unit_X :: R2
- unit_Y :: R2
- direction :: Angle a => R2 -> a
- fromDirection :: Angle a => a -> R2
- e :: Angle a => a -> R2
- tau :: Floating a => a
- class Num a => Angle a where
- toCircleFrac :: a -> CircleFrac
- fromCircleFrac :: CircleFrac -> a
- newtype CircleFrac = CircleFrac {}
- newtype Rad = Rad {}
- newtype Deg = Deg {}
- fullCircle :: Angle a => a
- convertAngle :: (Angle a, Angle b) => a -> b
- stroke :: Renderable (Path R2) b => Path R2 -> Diagram b R2
- stroke' :: (Renderable (Path R2) b, IsName a) => StrokeOpts a -> Path R2 -> Diagram b R2
- strokeT :: Renderable (Path R2) b => Trail R2 -> Diagram b R2
- strokeT' :: (Renderable (Path R2) b, IsName a) => StrokeOpts a -> Trail R2 -> Diagram b R2
- data FillRule
- fillRule :: HasStyle a => FillRule -> a -> a
- data StrokeOpts a = StrokeOpts {
- vertexNames :: [[a]]
- queryFillRule :: FillRule
- clipBy :: (HasStyle a, V a ~ R2) => Path R2 -> a -> a
- hrule :: (PathLike p, V p ~ R2) => Double -> p
- vrule :: (PathLike p, V p ~ R2) => Double -> p
- unitCircle :: (Backend b R2, Renderable Ellipse b) => Diagram b R2
- circle :: (Backend b R2, Renderable Ellipse b) => Double -> Diagram b R2
- circlePath :: (PathLike p, Closeable p, V p ~ R2, Transformable p) => Double -> p
- ellipse :: (Backend b R2, Renderable Ellipse b) => Double -> Diagram b R2
- ellipseXY :: (Backend b R2, Renderable Ellipse b) => Double -> Double -> Diagram b R2
- arc :: (Angle a, PathLike p, V p ~ R2) => a -> a -> p
- wedge :: (Angle a, PathLike p, V p ~ R2) => Double -> a -> a -> p
- polygon :: (PathLike p, V p ~ R2) => PolygonOpts -> p
- polyVertices :: PolygonOpts -> [P2]
- data PolygonOpts = PolygonOpts {}
- data PolyType
- data PolyOrientation
- data StarOpts
- star :: StarOpts -> [P2] -> Path R2
- regPoly :: (PathLike p, V p ~ R2) => Int -> Double -> p
- eqTriangle :: (PathLike p, V p ~ R2) => Double -> p
- square :: (PathLike p, Transformable p, V p ~ R2) => Double -> p
- pentagon :: (PathLike p, V p ~ R2) => Double -> p
- hexagon :: (PathLike p, V p ~ R2) => Double -> p
- septagon :: (PathLike p, V p ~ R2) => Double -> p
- octagon :: (PathLike p, V p ~ R2) => Double -> p
- nonagon :: (PathLike p, V p ~ R2) => Double -> p
- decagon :: (PathLike p, V p ~ R2) => Double -> p
- hendecagon :: (PathLike p, V p ~ R2) => Double -> p
- dodecagon :: (PathLike p, V p ~ R2) => Double -> p
- unitSquare :: (PathLike p, V p ~ R2) => p
- rect :: (PathLike p, Transformable p, V p ~ R2) => Double -> Double -> p
- roundedRect :: (PathLike p, V p ~ R2) => R2 -> Double -> p
- text :: Renderable Text b => String -> Diagram b R2
- font :: HasStyle a => String -> a -> a
- fontSize :: HasStyle a => Double -> a -> a
- italic :: HasStyle a => a -> a
- oblique :: HasStyle a => a -> a
- bold :: HasStyle a => a -> a
- image :: Renderable Image b => FilePath -> Double -> Double -> Diagram b R2
- rotation :: Angle a => a -> T2
- rotate :: (Transformable t, V t ~ R2, Angle a) => a -> t -> t
- rotateBy :: (Transformable t, V t ~ R2) => CircleFrac -> t -> t
- rotationAbout :: Angle a => P2 -> a -> T2
- rotateAbout :: (Transformable t, V t ~ R2, Angle a) => P2 -> a -> t -> t
- scalingX :: Double -> T2
- scaleX :: (Transformable t, V t ~ R2) => Double -> t -> t
- scalingY :: Double -> T2
- scaleY :: (Transformable t, V t ~ R2) => Double -> t -> t
- scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation v
- scale :: (Transformable t, Fractional (Scalar (V t))) => Scalar (V t) -> t -> t
- scaleToX :: (Boundable t, Transformable t, V t ~ R2) => Double -> t -> t
- scaleToY :: (Boundable t, Transformable t, V t ~ R2) => Double -> t -> t
- scaleUToX :: (Boundable t, Transformable t, V t ~ R2) => Double -> t -> t
- scaleUToY :: (Boundable t, Transformable t, V t ~ R2) => Double -> t -> t
- translationX :: Double -> T2
- translateX :: (Transformable t, V t ~ R2) => Double -> t -> t
- translationY :: Double -> T2
- translateY :: (Transformable t, V t ~ R2) => Double -> t -> t
- translation :: HasLinearMap v => v -> Transformation v
- translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> t
- reflectionX :: T2
- reflectX :: (Transformable t, V t ~ R2) => t -> t
- reflectionY :: T2
- reflectY :: (Transformable t, V t ~ R2) => t -> t
- reflectionAbout :: P2 -> R2 -> T2
- reflectAbout :: (Transformable t, V t ~ R2) => P2 -> R2 -> t -> t
- strutX :: (Backend b R2, Monoid m) => Double -> AnnDiagram b R2 m
- strutY :: (Backend b R2, Monoid m) => Double -> AnnDiagram b R2 m
- (===) :: (HasOrigin a, Boundable a, V a ~ R2, Monoid a) => a -> a -> a
- (|||) :: (HasOrigin a, Boundable a, V a ~ R2, Monoid a) => a -> a -> a
- hcat :: (HasOrigin a, Boundable a, V a ~ R2, Monoid a) => [a] -> a
- hcat' :: (HasOrigin a, Boundable a, V a ~ R2, Monoid a) => CatOpts R2 -> [a] -> a
- vcat :: (HasOrigin a, Boundable a, V a ~ R2, Monoid a) => [a] -> a
- vcat' :: (HasOrigin a, Boundable a, V a ~ R2, Monoid a) => CatOpts R2 -> [a] -> a
- alignL :: (HasOrigin a, Boundable a, V a ~ R2) => a -> a
- alignR :: (HasOrigin a, Boundable a, V a ~ R2) => a -> a
- alignT :: (HasOrigin a, Boundable a, V a ~ R2) => a -> a
- alignB :: (HasOrigin a, Boundable a, V a ~ R2) => a -> a
- alignTL, alignBR, alignBL, alignTR :: (HasOrigin a, Boundable a, V a ~ R2) => a -> a
- alignX :: (HasOrigin a, Boundable a, V a ~ R2) => Double -> a -> a
- alignY :: (HasOrigin a, Boundable a, V a ~ R2) => Double -> a -> a
- centerX :: (HasOrigin a, Boundable a, V a ~ R2) => a -> a
- centerY :: (HasOrigin a, Boundable a, V a ~ R2) => a -> a
- centerXY :: (HasOrigin a, Boundable a, V a ~ R2) => a -> a
- width :: (Boundable a, V a ~ R2) => a -> Double
- height :: (Boundable a, V a ~ R2) => a -> Double
- size2D :: (Boundable a, V a ~ R2) => a -> (Double, Double)
- extentX :: (Boundable a, V a ~ R2) => a -> (Double, Double)
- extentY :: (Boundable a, V a ~ R2) => a -> (Double, Double)
- center2D :: (Boundable a, V a ~ R2) => a -> P2
- data SizeSpec2D
- showOrigin :: (Renderable Ellipse b, Backend b R2, Monoid m) => AnnDiagram b R2 m -> AnnDiagram b R2 m
- showLabels :: (Renderable Text b, Backend b R2) => AnnDiagram b R2 m -> AnnDiagram b R2 Any
R^2
type T2 = Transformation R2Source
Transformations in R^2.
direction :: Angle a => R2 -> aSource
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 a => a -> R2Source
Convert an angle into a unit vector pointing in that direction.
A convenient synonym for fromDirection.
Angles
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.
newtype CircleFrac Source
Newtype wrapper used to represent angles as fractions of a circle. For example, 13 = tau3 radians = 120 degrees.
Constructors
| CircleFrac | |
Fields | |
Newtype wrapper for representing angles in radians.
Newtype wrapper for representing angles in degrees.
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, IsName 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' syntax may be used.
with {
... }
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, IsName a) => StrokeOpts a -> Trail R2 -> Diagram b R2Source
A composition of stroke' and pathFromTrail for conveniently
converting a trail directly into a diagram.
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 -> aSource
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 notation.
with { ... }
Constructors
| StrokeOpts | |
Fields
| |
Instances
| Default (StrokeOpts a) |
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.
circlePath :: (PathLike p, Closeable p, V p ~ R2, Transformable p) => Double -> pSource
Create a closed circular path of the given radius, centered at the origin, beginning at (r,0).
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, is the
path of a radius one arc counterclockwise between the two angles.
arc s e
wedge :: (Angle a, PathLike p, V p ~ R2) => Double -> a -> a -> pSource
Create a circular wedge of the given radius, beginning at the first angle and extending counterclockwise to the second.
General polygons
polyVertices :: PolygonOpts -> [P2]Source
Generate the vertices of a polygon. See PolygonOpts for more
information.
data PolygonOpts Source
Options for specifying a polygon.
Constructors
| PolygonOpts | |
Fields
| |
Instances
| Default PolygonOpts | The default polygon is a regular pentagon of radius 1, centered at the origin, aligned to the x-axis. |
Method used to determine the vertices of a polygon.
Constructors
| forall a . Angle a => PolyPolar [a] [Double] | A "polar" polygon.
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 |
| forall a . Angle a => PolySides [a] [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.
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
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 R2Source
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 PathLike. But of course
the list can be generated any way you like. A is
returned (instead of any Path R2PathLike) 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 :: (PathLike p, V p ~ R2) => Int -> Double -> pSource
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.
eqTriangle :: (PathLike p, V p ~ R2) => Double -> pSource
An equilateral triangle, with sides of the given length and base parallel to the x-axis.
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.
pentagon :: (PathLike p, V p ~ R2) => Double -> pSource
A regular pentagon, with sides of the given length and base parallel to the x-axis.
hexagon :: (PathLike p, V p ~ R2) => Double -> pSource
A regular hexagon, with sides of the given length and base parallel to the x-axis.
septagon :: (PathLike p, V p ~ R2) => Double -> pSource
A regular septagon, with sides of the given length and base parallel to the x-axis.
octagon :: (PathLike p, V p ~ R2) => Double -> pSource
A regular octagon, with sides of the given length and base parallel to the x-axis.
nonagon :: (PathLike p, V p ~ R2) => Double -> pSource
A regular nonagon, with sides of the given length and base parallel to the x-axis.
decagon :: (PathLike p, V p ~ R2) => Double -> pSource
A regular decagon, with sides of the given length and base parallel to the x-axis.
hendecagon :: (PathLike p, V p ~ R2) => Double -> pSource
A regular hendecagon, with sides of the given length and base parallel to the x-axis.
dodecagon :: (PathLike p, V p ~ R2) => Double -> pSource
A regular dodecagon, with sides of the given length and base parallel to the x-axis.
Other special polygons
unitSquare :: (PathLike p, V p ~ R2) => pSource
A sqaure with its center at the origin and sides of length 1, 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.
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.
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 (1/4 :: , CircleFrac)rotate (tau/4 :: , and
Rad)rotate (90 :: all represent the same transformation, namely,
a counterclockwise rotation by a right angle.
Deg)
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 (1/4) than .
rotate (1/4 :: 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.
scaleUToX :: (Boundable t, Transformable t, V t ~ R2) => Double -> t -> tSource
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 :: (Boundable t, Transformable t, V t ~ R2) => Double -> t -> tSource
scaleUToY h scales a diagram in the y (vertical) direction by
whatever factor required to make its height h. scaleUToY
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
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).
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, height 0, and a
centered local origin. 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, width 0, and a
centered local origin. 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, 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
alignToralignB) from Diagrams.TwoD.Align before applyinghcat. - For non-axis-aligned layout, see
cat.
vcat :: (HasOrigin a, Boundable 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
alignLoralignR) from Diagrams.TwoD.Align before applyingvcat. - For non-axis-aligned layout, see
cat.
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.
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 1moves the local origin to the right edge; - any other argument interpolates linearly between these. For
example,
alignX 0centers,alignX 2moves 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
size2D :: (Boundable a, V a ~ R2) => a -> (Double, Double)Source
Compute the width and height of a boundable object.
extentX :: (Boundable a, V a ~ R2) => a -> (Double, Double)Source
Compute the absolute x-coordinate range of a boundable object 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 boundable object 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 boundable object.
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.
showLabels :: (Renderable Text b, Backend b R2) => AnnDiagram b R2 m -> AnnDiagram b R2 AnySource