diagrams Reference

(the Haskell library)

diagrams is a nifty Haskell library for making vector diagrams. I keep coming back to it to generate graphics for puzzles:

I got sick of relearning it every time, and I think there’s some small chance other people will find it useful too, so I wrote something up. This post is a sort of reference that tries to compromise between the quick start tutorial and manual on one hand, and the API reference on the other, to try to be deeper and more comprehensive than the former, but also flow better and be easier to navigate than the latter. Some types are just really intimidating when fully written out…

To avoid unhelpfully generic types, I will deal concretely with two-dimensional diagrams that measure everything in Double, and will frequently abbreviate complex types with an asterisk, like I will write V2* for V2 Double. I will introduce these aliases along the way for easy greppability. They’re not legal Haskell, of course.

This reference assumes basic-to-intermediate Haskell knowledge. Some of the more intermediate stuff includes:

  • Monoids, and that the Haskell Monoid operator is <>
  • Typeclasses. I will sometimes write fake type signatures as abbreviations for typeclass restrictions: for example, TrailLike is a typeclass, and I might say or write that a function returns TrailLike when I really mean TrailLike t => t, any type t that is in that typeclass.

van Laarhoven lenses may help, but mostly I’ll try to black-box them.

Basic Types

Haddock reference: Diagrams.TwoD.Types.

  • Vectors: V2 Double (which I’ll abbreviate V2*) is the standard two-coordinate vector type. By default, the first coordinate x goes right and the second coordinate y goes up (as is typical in mathematics, but not graphics — tells your something about the provenance of this library). This type actually comes from the linear package, which shows you how deep the rabbit hole goes.

    V2* is Additive, which gives you:

    • zero :: V2*
    • negated :: V2* -> V2*
    • vector-vector operations ^+^, ^-^
    • vector-scalar operations *^, ^*, ^/ (the vector goes on the side of the ^)
    • lerp :: Double -> V2* -> V2* -> V2* (linear interpolation, 0 is the first vector and 1 is the second)

    among others. It’s also Num, so you can directly do arithmetic between vectors, which vectorizes componentwise (e.g. V2 x y * V2 x' y' == V2 (x * x') (y * y')). You can directly construct and pattern-match as V2 x y, or use r2 :: (Double, Double) -> V2 Double or its inverse unr2. Provided constants include basis vectors unitX, unitY :: V2* and their negations unit_X, unit_Y :: Double (which I can’t really recommend because they look really confusing). (Lenses: there’s the isomorphisms r2Iso :: Iso' (V2*) (Double, Double), and Linear.V2 provides lenses _x and _y if you want them.)

    Linear.Metric has some functions for measuring vectors and doing other metric space operations, among them norm :: V2* -> Double, quadrance :: V2* -> Double (norm squared, slightly more efficient), normalize :: V2* -> V2* (convert to unit vector or zero), dot :: V2* -> V2* -> Double, and project :: V2* -> V2* -> V2*.

  • Points: Point V2 Double (synonymized as P2 Double, I’ll abbreviate P2*) is the type of a point, distinguished from a vector at the type level. (It’s also from linear, Linear.Affine.) Convert from/to coordinates with p2 :: (Double, Double) -> P2* and inverse unp2; origin :: P2* is the, well, origin. P2* is also Additive so you can still add and subtract points, but I would say that semantically, you probably shouldn’t, although interpolation makes sense. Instead, Linear.Affine gives you operators (.-.) :: P2* -> P2* -> V2* and (.+^), (.-^) :: P2* -> V2* -> P2* (the vector still goes on the side of the ^, the point goes on the side of the .). You can probably also use translate :: V2* -> P2* -> P2*; see Transform. (Lenses: there’s the isomorphisms p2Iso :: Iso' (P2*) (Double, Double), and the same lenses _x and _y work by typeclass stuff.)

  • Angles (Diagrams.Angle): Angle Double (which I’ll call Angle*, internally just a newtype over Double) is the, well, angle type. In keeping with the mathematical flavor, angles are measured counterclockwise, starting from the positive x-axis when that’s relevant. diagrams provides van Laarhoven isomorphisms turn, rad, deg, which means you can construct an angle as ((1/3) @@ turn) and deconstruct with ^., like a ^. rad. ((@@) is a diagrams custom operator that’s just flipped review for a van Laarhoven Review, which an isomorphism is, because an isomorphism is everything.) Constant angles include fullTurn and halfTurn; angles are also Additive, so you can use the operators (^+^), (^-^), negated, (*^), (^*), (^/) from above on them too.

  • Directions (Diagrams.Direction): Direction V2 Double (I’ll abbreviate Direction*) is a vector without the magnitude. You can convert from a vector with direction :: V2* -> Direction*, convert a direction to a unit vector with fromDirection :: Direction* -> V2*, and do a few other operations, but most functions that use directions have versions that work with vectors instead, so I won’t go into depth in these. I’m just mentioning it for completeness.

The vectors and points guide has lots more stuff.

Segments, Trails, Paths, Diagrams

From points, we can make more complex structures.

  • Segments (Diagrams.Segment): A Segment Closed V2 Double (Segment*) is basically an “atomic path” that can’t be broken down further. It has no location and describes relative movement only. Brief types: straight :: V2* -> Segment*, bezier3 :: V2* -> V2* -> V2* -> Segment* (construct a bezier starting at the origin with those two control points and the third as the endpoint). There are more helpers there, but other than those two, you should rarely need to use them. You will rarely need to manipulate segments directly and can usually just work at trails or higher abstractions.

  • Trails (Diagrams.Trail): A trail is, roughly, a list of segments, semantically concatenated so each one starts where the previous one ends. It still does not have location and describes relative movement only. It can be closed, Trail' Loop V2 Double (I’ll call it Loop*) or open, Trail' Line V2 Double (I’ll call it Line*). An un-primed Trail V2 Double (I’ll call it Trail*) existentially holds one or the other. I’ll also denote Trail'* as “either Loop* or Line*” (implemented with a typeclass). You can convert between them as:

    • wrapLine :: Line* -> Trail*, wrapLoop :: Loop* -> Trail*, wrapTrail :: Trail'* -> Trail*
    • cutLoop :: Loop* -> Line* cuts the loop at its starting point, making that “coincidentally” both the start and the end.
    • closeLine, glueLine :: Line* -> Loop*: The first adds a line segment from the last point to the start; the second forcibly moves the last point to the start, but you should use it if you constructed a Line you know is Really Closed so as not to add a length-0 segment.

    There are many functions for destructing trails/loops/lines, but most of them are rarely useful, so I will just mention two sets of functions:

    • trailVertices/lineVertices/loopVertices convert a Located Trail*/Line*/Loop* to a list of vertices [P2*], roughly the points at which the curve is not differentiable. For a loop, the resulting list doesn’t contain the starting/ending point twice (only at the start, not at the end); cutLoop if you do want it twice. Located (Diagrams.Located) really just means “with an accompanying absolute position” (literally, it’s a data with two fields, check the docs if you want); the fields are loc and unLoc, and one can be constructed with at :: a -> P2* -> Located a (meant to be used infix). However, you may not need to touch it at all; see the next section.
    • explodeTrail :: Located Trail* -> [Located Trail*] deconstructs a trail into smaller trails, one per segment. (Note: Even with a fixed vector space, that type is fake and the real type is far more polymorphic; see the next section.)

    I also want to mention reverseTrail/reverseLine/reverseLoop, which do what you expect.

    Line* is a Monoid with start-where-the-previous-ends concatenation. Loop* is not a Monoid, but Trail is a Monoid that does cutLoop if necessary and then concatenates the Line*s, with a special case to make the empty Line* a true identity.

    (You’ll note I haven’t described how to make a trail from segments. It’s because the functions for doing that are too polymorphic. See the next section.)

  • Paths (Diagrams.Path: A path is a collection of located trails (i.e., trails with accompanying absolute positions; see above). Path’s type is Path V2 Double, which I’ll abbreviate Path*. You can pathFromTrailAt :: Trail* -> Point* -> Path*. Path* is a Monoid by superposition.

  • Diagrams: A diagram is… well, it depends on the backend, exactly, but it’s basically “something you can render to a screen”. Type QDiagram b V2 Double Any, or just Diagram b, where b is the “backend” you’re using and can just be written B in the usual setup — the idea is that you can switch what backend to use just by changing a package import. I’ll just call it Diagram*. Diagram* is also a Monoid by superposition. (A slightly annoying thing: a <> b has a above b by “z-index”, which makes sense, except that this implies a will be after b in the SVG output, which can make you sad if you care about, say, allowing good copy-paste from the SVG. The result is similar for other combinators.)

    The abstractions before the diagram have no concept of color or line width or anything of the sort, they’re all just infinitesimal abstract lines and curves in space. To convert them to a diagram, call one of the “stroke” functions in Diagrams.TwoD.Path: strokeLine, strokeLoop, strokeTrail, strokePath take what you’d expect and convert it to a Diagram.

    Note: Don’t confuse “stroke” with the concept of stroking in other graphics terminology, where you draw along a path as opposed to filling it. There is no separate function to fill a line/loop/trail. Instead, you “stroke” it to convert it to a diagram with a default line width and fill style, set the line width to none, and set the fill style to whatever you want.

    I will also mention an additional instantiation of Diagram: Diagram NullBackend V2 Double, aliased D V2 Double, is a diagram that lacks that a backend and cannot be rendered. This type is still occasionally useful to write out explicitly when you want to create a diagram and then measure it somehow without rendering it; Haskell might complain that it’s underspecified.

TrailLike

So why did I skip explaining how to construct a trail? It’s because most functions that do so directly construct a “trail-like object” (Diagrams.TrailLike). It’s specified by a typeclass, TrailLike t => t (sometimes with additional constraints, but they usually won’t matter; now denoted TrailLike*), and can be any of a Line*, Loop*, Trail*, Path*, Diagram*, or others, including Located variants of any of them. (cutLoop and glueLine are used to coerce a trail into a Line* or Loop* if it’s actually the other kind.) Even [P2], a list of points, is TrailLike — which is why you might not need to use trailVertices and friends at all. (Some TrailLikes have an absolute position and some don’t, so depending on what return type you use, if you pass absolute positions into the following functions they might or might not matter!)

The functions to construct trails or any of the other abstractions above it:

  • fromOffsets :: [V2*] -> TrailLike*
  • fromVertices :: [P2*] -> TrailLike*
  • fromSegments :: [Segment] -> TrailLike*
  • (~~) :: P2* -> P2* -> TrailLike*: one line segment between two points
  • advanced: cubicSpline, bspline

There are also many slightly high-level shapes, see Diagrams.TwoD.Shapes and Diagrams.TwoD.Ellipse. All the following shapes are centered at the origin.

  • circle :: Double -> TrailLike* constructs a circle from its radius. unitCircle :: TrailLike* is a convenience.
  • triangle, square, pentagon, ..., dodecagon :: Double -> TrailLike* and regPoly :: Int -> Double -> TrailLike* construct regular polygons from a side length (oriented to have a “bottom edge”, the one with lowest y, parallel to the x-axis). unitSquare :: TrailLike* is a convenience.
  • rect :: Double -> Double -> TrailLike* (width, then height) constructs a rectangle.
  • hrule, vrule :: Double -> TrailLike* construct horizontal and vertical line segments.

Read the manual for more exotic shapes like rounded rectangles. Diagrams.TwoD.Polygons generates regular and other polygons with much more customizability and, in particular, lets you set the radius instead of the side length.

Modifying All The Above Stuff

You can apply affine transformations (which include translations, rotations, reflections, and scaling/homotheties) to all the above stuff (Diagrams.TwoD.Transform). Transformations preserve type, so monomorphizing these would suck; below, tf will be a type variable for approximately any transformable type (with typeclass in fact called Transformable). The common transformation functions are:

  • rotate :: Angle* -> tf -> tf; rotateBy :: Double -> tf -> tf is a convenience that takes units of full revolutions.
  • scaleX, scaleY, scale :: Double -> tf -> tf
  • translateX, translateY :: Double -> tf -> tf; translate :: V2* -> tf -> tf
  • reflectX, reflectY, reflectXY :: tf -> tf. Note reflectXY sends (x,y) to (y,x).

There is also a type Transformation V2 Double (or T2 Double) representing a reified affine transformation, which you can get by calling variants of the above functions with nouns as names, maybe store somewhere or do other fun transform-y stuff with, and then transform :: T2* -> tf -> tf.

Note that affine transformations always act uniformly on line widths and other measures, no matter the orientation of the line. For example, if you attach a constant line width to a square and then stretch it into a rectangle, the rectangle will still have a constant line width all the way around it, instead of the short side becoming thicker. This is usually what you want anyway. (If the line width is in units that the transformation can affect, it gets scaled by the square root of the determinant. That’s just what you’d intuitively expect it to be.)

(Measures are covered in a later section.)

Combining Diagrams

We already know that diagrams are a monoid by superposition, and technically with superposition and transformations you should already be able to draw anything you want, but it’s not nice.

Where diagrams really shines is combining diagrams declaratively. You might think, “put this circle to the left of this square” or “draw an arrow from this circle to this circle”, and you can express this very simply in diagrams. This is implemented using the envelope, which is covered in more detail later. The packages Diagrams.Combinators and Diagrams.TwoD.Combinators have a bunch of functions:

  • atop :: Diagram* -> Diagram* -> Diagram* or the typical monoid <> stick on top of each other (and so mconcat superimposes a list). (beneath is flipped, if you ever have a diagram that constructs more naturally that way.)
  • beside :: V2* -> Diagram* -> Diagram* -> Diagram*, and (|||), (===) :: Diagram* -> Diagram* -> Diagram* put two diagrams “next to” each other in a direction v :: V2* in the following sense: the second diagram is translated in the direction of v as little as possible such that there exists a line perpendicular to v separating the two diagrams. See the quickstart guide on envelopes (and the sections before it) for an example.

    For (|||), v goes right, and for (===), v goes down; the idea is to be sort of self-illustrating:

                 a
    a ||| b     ===
                 b

    The n-ary versions are cat :: V2* -> [Diagram*] -> Diagram*, hcat, vcat :: [Diagram*] -> Diagram*. For all those “beside” combinators, the origin is still the first or the left-hand-side diagram’s origin.

    There’s also appends :: Diagram* -> [(V2*, Diagram*)] -> Diagram*, which is a “simultaneous beside”: it simultaneously places all the diagrams in the list next to the first diagram in the accompanying direction, but without diagrams in the list affecting each other.

  • Sometimes you want diagrams almost next to each other, but separated by some space. hsep, vsep :: Double -> [Diagram*] -> Diagram* separate the diagrams by that much space. cat' is a more generalized version with a lensed options data type. If v :: V2*, d :: Double, and a :: [Diagram*], then:

    • cat' v (with & catMethod .~ Cat & sep .~ d) a puts all the diagrams next to each other in the direction of v, separated by d.
    • cat' v (with & catMethod .~ Distrib & sep .~ d) a doesn’t look at the envelopes at all; it just puts all the diagrams in a row in that direction, with each origin distance d from the previous. (So if d = 0 it’s just superposition again.)
  • As the last cat' overloading shows, you don’t always want to combine diagrams by their envelopes. position :: [(P2*, Diagram*)] -> Diagram* and atPoints :: [P2*] -> [Diagram*] -> Diagram* just combine a bunch of diagrams by putting their origins at certain locations.

The same packages also have some empty objects and some functions for adding space around a diagram:

  • withEnvelope :: Diagram* -> Diagram* -> Diagram* produces a diagram with the left diagram as its envelope, but the right diagram as its output.
  • phantom :: Diagram* -> Diagram* produces a diagram with the same envelope and trace, but no output; it’s completely invisible.
  • strut :: V2* -> Diagram* produces an invisible line segment (i.e. the envelope is a line segment but the digram is invisible). However, strut lacks a trace, if you ever use tracing.
  • strutR2 :: V2* -> Diagram* does the same except with a trace. (Both exist because strut also works for higher dimensions and I oversimplified its type here.)
  • strutX, strutY :: Double -> Diagram* produce horizontal and vertical invisible line segments.
  • pad :: Double -> Diagram* -> Diagram* proportionally expands/contracts the envelope wrt the origin. (The Double is the proportion, so pad 2 on a 1×2 rectangle results in a 2×4-sized thing.)
  • frame :: Double -> Diagram* -> Diagram* adds an absolute amount of space in all directions.

Finally, there’s a few functions for working with bounding rectangles:

  • boundingRect :: Diagram* -> TrailLike* gives you the rectangle that bounds the diagram as any TrailLike.
  • bg :: Colour Double -> Diagram* -> Diagram* superimposes the diagram into a filled rectangle of that color (and no line width).
  • bgFrame :: Double -> Colour Double -> Diagram* -> Diagram* combines bg and frame. I know I haven’t covered colors yet, but it makes the most sense here, and it’s a good segue into the next section:

Bounding and Sizing

Diagrams.Size and Diagrams.TwoD.Size have some functions for measuring and resizing a diagram along the coordinate axes.

The mildly hidden size :: Diagram* -> V2* from Diagrams.Core.Envelope computes a vector containing the width and height of the diagram; the functions width, height :: Diagram* -> Double from Diagrams.TwoD.Size give the components.

For more structure, Diagrams.Size defines the type (that specializes into) SizeSpec V2 Double, which I’ll call SizeSpec* and which basically holds an optional width and height. You can construct one with dims :: V2* -> SizeSpec*, dims2D :: Double -> Double -> SizeSpec*, mkWidth, mkHeight :: Double -> SizeSpec*, or absolute :: SizeSpec*. You can use sized :: SizeSpec* -> Diagram* -> Diagram* to resize a diagram to fit the spec, or sizedAs :: Diagram* -> Diagram* -> Diagram* to resize the second diagram to fit inside the bounding box of the first. (This does not change the aspect ratio of the diagram, so e.g. resizing a 1×2 rectangle into a unit square will give you a 0.5×1 rectangle. It also does not do any translation. Optional and nonpositive dimensions are ignored, so e.g. sized (mkWidth w) will resize a Diagram* so that it has width w and height whatever is necessary to preserve the aspect ratio.)

BoundingBox defines a type BoundingBox V2 Double, which I’ll just abbreviate BoundingBox*. Unlike a SizeSpec, a BoundingBox has a location, but the box can also be empty, so BoundingBox has an optional layer in its internal representation. I think the most useful methods are boundingBox :: Diagram* -> BoundingBox* and boxFit :: BoundingBox* -> Diagram* -> Diagram*, which rectilinearly transforms the diagram to have exactly that bounding box and may change the aspect ratio.

Envelopes and Traces

The sizes and bounding boxes in the preceding section actually all just use special cases of the envelope, the same feature used to put diagrams beside each other. Haddock: Diagrams.Envelope.

The envelope extensionally tracks, for every orientation, the two closest lines in that orientation that would sandwich the diagram; another way to see it is that it projects the diagram onto a single dimension and takes the two points that are furthest apart. So, a shape has the same envelope as its convex hull. “Extensionally” means that it’s just a function, not some data structure of numbers. The envelope is used for beside and company; so when you put two things next to each other with, say, |||, you’ll always be able to draw a vertical line in the resulting diagram that separates the two envelopes.

The diagram is a little cruder than the trace, which roughly lets you perform ray tracing: given any ray, i.e. any point and any direction, find all intersections of that ray with the figure. Haddock: Diagrams.Trace.

Debugging

Diagrams.TwoD.Model has some “debugging” helpers: showOrigin, showEnvelope, showTrace :: Diagram* -> Diagram* are simple functions to visually see where the origin, envelope and trace of a diagram is. There are customizable versions in that module as well.

Aligning

Diagrams.Align and Diagrams.TwoD.Align have functions for moving a diagram’s local origin to somewhere, typically the edge of its envelope or a center. The one I use the most often is center :: Diagram* -> Diagram*, which just centers a diagram at the center of its bounding box.

  • align :: V2* -> Diagram* -> Diagram* moves the origin in that direction until it lies on the envelope; centerV :: V2* -> Diagram* -> Diagram* moves the origin parallel to that direction so it’s halfway between the edges.
  • alignX :: Double -> Diagram* -> Diagram* moves the origin horizontally to a fraction between the left and right edge of the boundary: −1 for the left edge, 0 for the center, 1 for the right edge.
  • alignY :: Double -> Diagram* -> Diagram* moves the origin vertically to a fraction between the bottom and top edge of the boundary: −1 for the bottom edge, 0 for the center, 1 for the top edge.
  • alignL, alignR, alignT, alignB, alignTL, alignTR, alignBL, alignBR, centerX, centerY, centerXY :: Diagram* -> Diagram* move the local origin horizontally, vertically, or both, to an edge or center. (center and centerXY are the same in two dimensions.)

Styling

The graphic aspects of diagrams — color, line width, and so on — are attributes and defined in Diagrams.Attributes and Diagrams.TwoD.Attributes.

Color

Color is mostly outsourced to the colour package (note the British spelling). Many standard colors — think black, red, etc. all of type Colour Double — are automatically exported from Data.Colour.Names. Data.Colour.SRGB has other functions. The most convenient way to write an arbitrary color is likely sRGB24read :: String -> Colour Double from Data.Colour.SRGB, which takes a hex string like "#00aaff". You can also use sRGB :: Double -> Double -> Double -> Colour Double. Blending color can be achieved with blend :: Double -> Colour Double -> Colour Double (0 to 1). Should you want HSL or HSV, I think the way to get them is Data.Colour.RGBSpace.HSL’s hsl :: Double -> Double -> Double -> RGB Double or Data.Colour.RGBSpace.HSV’s hsv :: Double -> Double -> Double -> RGB Double, uncurryRGB :: (a -> a -> a -> b) -> RGB a -> b, and sRGB :: Double -> Double -> Double -> Colour Double. I think this is difficult because of stuff with color representation I haven’t really dug into. The AlphaColour Double is a slightly expanded color type that comes with an alpha channel.

diagrams functions generally take Color c => c (note the American spelling). Color is a diagrams typeclass filled by Colour Double, AlphaColour Double, and the existentially-one-or-the-other SomeColor. I’ll just abbreviate this as Color*.

Measure

Measure (Diagrams.Core.Measure) is the data type diagrams uses to represent line width, among other things. Internally, a measure can be any function (Double, Double, Double) -> Double, which takes a “local scale”, a “normalized scale”, and a “global scale”; I mention this not because you need to think of it this way but to emphasize how flexible it is.

  • “Local” units (local :: Double -> Measure*) are measured in the diagram’s current vector space. These are the only units that aren’t scale-invariant.
  • “Global” units (global :: Double -> Measure*) are measured in the diagram’s final vector space.
  • “Normalized” units (normalized, normalised :: Double -> Measure*) are measured as fractions of the diagram’s final dimensions.
  • “Output” units (output :: Double -> Measure*) are measured in whatever absolute units the diagram is ultimatedly rendered in, for example, pixels.

So, as an example, if you have a 10×10 square stroked with a line width of 1 “unit”, you scale it up by 10×, and then you render this as a 1000×1000 image:

  • 1 local unit would be 10 units in the final vector space, which is 100 pixels;
  • 1 global unit would be 1 unit in the final diagram space, which is 10 pixels;
  • 1 normalized unit would be the dimension of the final image, which is 1000 pixels;
  • 1 output unit would be exactly 1 pixel.

Line widths, line colors, fill colors

Diagrams.Attributes defines a lot of default measures. There’s thin, medium, thick, which are the maximum of some normalized value and 0.5 output units; small, normal, large, which are just some normalized value; a bunch of variants I won’t list; and none, a zero measure. And it defines the function lw :: Measure -> Diagram* -> Diagram* to set the line width of a diagram, and lwG, lwN, lwO, lwL :: Double -> Diagram* -> Diagram* as shorthand to use each of the above units.

Diagrams.TwoD.Attributes has all the color-using functions:

  • Line color: lc :: Colour Double -> Diagram* -> Diagram* and lcA :: AlphaColour Double -> Diagram* -> Diagram*
  • Fill color: fc :: Colour Double -> Diagram* -> Diagram* and fcA :: AlphaColour Double -> Diagram* -> Diagram*

When you apply any of these functions lw, lc, fc to a diagram, you apply it to every subdiagram that hasn’t had that particular attribute set yet.

Names and Subdiagrams

Haddock: Diagrams.Names.

You can name a diagram with named :: IsName nm => nm -> Diagram* -> Diagram*.

  • What things are IsName? Most “value-y” things are names, including strings, integers, and small tuples thereof; it’s also super easy to define a type and derive your own. See Named Subdiagrams in the manual. This gets existentially reified into the data type Name.
  • What’s the point of a name? It enables you to look up a Subdiagram* later, with lookupName :: Name -> Diagram* -> Maybe (Subdiagram*), or do it in an inner function with withName :: Name -> (Subdiagram* -> Diagram* -> Diagram*) -> Diagram* -> Diagram*.

    You can extract the location where the diagram’s local origin ended up with location :: Subdiagram* -> P2*. You can also query its envelope and trace in various ways.

    Quite a few functions I covered that I said take Diagram*s also take Subdiagram*s, thanks to typeclasses. Some ones I would imagine being somewhat useful are the querying functions in Diagrams.Envelope and Diagrams.Trace.

  • Internally, names are actually sequences of “atomic names”; this is to help write qualified names. (.>) :: (IsName nm1, IsName nm2) => nm1 -> nm2 -> Name joins atomic components, and (.>>) :: Name -> Diagram* -> Diagram* pre-qualifies all names in a Diagram* with a name. localize :: Diagram* -> Diagram* hides all names in a diagram so they can’t be referred to from outside that call.

Arrows

Diagrams.TwoD.Arrow.

  • arrowV :: V2* -> Diagram*: arrow from origin with said displacement.
  • arrowAt :: P2* -> V2* -> Diagram*
  • arrowBetween :: P2* -> P2* -> Diagram*

  • connect :: Name* -> Name* -> Diagram* -> Diagram*: connect the origins of two subdiagrams
  • connectOutside :: Name* -> Name* -> Diagram* -> Diagram*: connect with an arrow on the line from origin to origin, but that starts and ends on the subdiagrams’ boundaries, computed with ray tracing
  • connectPerim :: Name* -> Name* -> Angle* -> Angle* -> Diagram* -> Diagram*: connect the points on the boundaries of two subdiagrams specified by the angles (counterclockwise from the positive x-axis).

All these have primed versions that take an ArrowOpts as an additional first argument. ArrowOpts is another lensed options type. An example option struct is (with & arrowHead .~ dart & arrowTail .~ dart).

Diagrams.TwoD.Arrowheads has a bunch of arrowheads (note that the arrowhead only specifies its shape, not its scale; set the headLength or tailLength option to customize that).

The arrows tutorial has actual examples.

Text

Haddock: Diagrams.TwoD.Text.

The simplest way to produce text is text :: String -> Diagram*, which is approximately centered. Note that this takes up no space. There’s also alignedText :: Double -> Double -> String -> Diagram*, but it doesn’t exactly work in the standard SVG backend; if you want something vertically centered, you might want to translateY by a small negative amount. I don’t have a great systematic solution; just eyeball it.

You can style text with these functions:

  • font :: String -> Diagram* -> Diagram* adds a font
  • fontSize :: Measure -> Diagram* -> Diagram* sets a font size
  • italic :: Diagram* -> Diagram*, oblique :: Diagram* -> Diagram*
  • bold :: Diagram* -> Diagram*

There are many other weights in this module.

Offset

I’ve never used the Diagrams.TwoD.Offset module, but it exists.

Output

I’ll focus on the SVG renderer.

The tutorial teaches you mainWith :: Diagram* -> IO () (from Diagrams.Backend.SVG.CmdLine; it’s actually way more polymorphic than that), which makes a program that lets you customize the diagram a lot with command-line options. But eventually I found that I preferred keeping more of the configuration inside the code.

Haddock: Diagrams.Backend.SVG

The simplest way to make your program produce an SVG is renderSVG :: FilePath -> SizeSpec* -> Diagram* -> IO () (FilePath is an alias for String). We saw SizeSpec* in the Bounding section, but I’ll reproduce the functions here:

  • dims :: V2* -> SizeSpec*
  • dims2D :: Double -> Double -> SizeSpec*
  • mkWidth, mkHeight :: Double -> SizeSpec*
  • absolute :: SizeSpec*

In particular absolute just means “just output whatever dimensions the diagram is in its units”.

Appendix: van Laarhoven lenses

There are entirely too many lenses tutorials out there and I don’t remember which of them are worth recommending, so I wrote somthing up.

Pretend we’re writing old-fashioned Java for a bit. Here’s a plain Java class:

Intuitively, Person has two “fields”, called name and age; and we might still say this as a description of Person’s public interface even if Person did not represent that data internally. That’s Encapsulation™! So, intuitively, a “field” is a pair of a getter and a setter.

In a language like Haskell, where stuff is immutable, the setter would instead be a function that takes a Person and a new name or age, and returns the updated Person. So Person’s interface would be shaped like this:

Conceptually, a lens is the idea of a “field” we just described. A lens from type s to type a is equivalent to a pair of a getter, a function of type s -> a, and a setter, a function of type s -> a -> s. And there are libraries that define a Lens s a as a simple data type that directly includes a pair of those functions, and provide utilities for working with them and composing them.

However, a more sophisticated approach is provided by van Laarhoven lenses. A van Laarhoven lens is defined as follows:

This is not at all intuitive, but this type is exactly isomorphic to having a getter and setter as described above. That is, given this type, you can implement a getter and setter, and vice versa. The key advantages are:

  • van Laarhoven lenses compose really nicely: it’s literally just function composition. That is, if you had some class Book with a field author of type Person, you can get a lens representing “the name field of the author field of the Book” just by composing the name field and author field lenses as ordinary functions.
  • You can define a universe of lens-like types (“optics”) with different constraints than Functor, which compose equally nicely and give you something exactly as strong as what you could have hoped for. The most interesting example is probably Prism' s a, which is isomorphic to a pair of functions a -> s and s -> Maybe a: it’s approximately the sum-product dual of a Lens', representing that s has a case of type a as well as possibly others. A more general optic is Traversal', which roughly represents a “(possibly empty) list of fields”. Every Lens' is a Traversal' that just happens to point to exactly one field, and every Prism' is a Traversal' that happens to point to at most one field that would also be enough to fully recover the original data. The key point is that you can compose any Lens', Prism', or Traversal' with any other in either order and get (at least) a Traversal'.

There are a lot of other optic types that look varying degrees of frivolous when you figure out what they’re isomorphic to and compare that to how intimidating their types are:

  • a Getter s a is isomorphic to a function s -> a.
  • a Fold s a is isomorphic to a function s -> [a] (though this is maybe an overly glib interpretation, since Foldable is isomorphic to toList but may have far more efficient and data-structure-specific implementations).
  • a Setter' s a is isomorphic to a function (a -> a) -> s -> s. Note that this is stronger than the intuitive “setter” we defined above, in that you can look at the old field value when deciding the new field value, but you still can’t “leak” it back to the caller (at least, without doing evil things to break Haskell’s purely functional nature); but also, that both this and the earlier definition allow you to set zero or multiple fields at once, which both make for a perfectly legal Setter' definition.
  • a Review s a is isomorphic to a function a -> s.
  • an Iso' s a is isomorphic to a pair of functions s -> a and a -> s (it’s, well, an isomorphism), and is every other optic mentioned so far.

(Why are some types primed with ' and some types aren’t? Because there are unprimed versions of some optics that may permit type-changing updates; a Lens' s a is really a Lens s s a a, where a Lens s t a b is isomorphic to a pair of functions s -> a and s -> b -> t. But that’s way more complexity than we need here.)

But to repeat, the point of all this is that you can compose different optics with different guarantees and end up with an optic with exactly the guarantees you could have hoped for. That type of optic will even have a name and you can easily (for some definition of “easily”) write functions that require optics to be exactly as strong as they need to be.

The key disadvantage is that the high-powered subtle type-level machinery that makes things work out this way nerd-snipes every type system aficionado into learning about it and working through it in their head when they could be writing production software. Also, the error messages are often bad.

Anyway, to get a normal function out of an optic, you can use any of these functions/operators from the lens library:

  • view g v or v ^. g gets with a Getter g
  • toListOf f v or v ^.. f gets the list of fields with a Fold f
  • preview p v or v ^? p gets the Maybe field pointed to by a Prism' p, or more generally the first field of a Fold
  • review r v reviews through a Review r (in the Lens library this is also provided as the operator #, but diagrams uses that for postfix application and provides @@ instead, as well as ##, a straight-up alias for #; # and ## are not flipped, but @@ is!)
  • over s f v or (s %~ f) v “updates” (all values) with a Setter s and a function f :: field -> field
  • set s x v or (s .~ x) v sets (all values) with a Setter s and a new field value x

There are hundreds more functions in the library: optics for common types, like _1 or _2 that are lenses pointing to a tuple’s components; functions for constructing optics like to, which turns a plain function into a Getter; shorthand operators for updating with common kinds of functions; a whole bunch of “indexed optics”. But the most common way you’ll probably use lenses in diagrams is to pass options to a function, in which case you really don’t need anything other than .~. with is an alias for def, the default type, and then you use lenses to update various parts of the options. See the diagrams manual on faking optional named arguments.

(note: the commenting setup here is experimental and I may not check my comments often; if you want to tell me something instead of the world, email me!)