diagrams-core-1.0: Core libraries for diagrams EDSL

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.Core.Types

Contents

Description

The core library of primitives forming the basis of an embedded domain-specific language for describing and rendering diagrams.

Diagrams.Core.Types defines types and classes for primitives, diagrams, and backends.

Synopsis

Diagrams

Annotations

type UpAnnots b v m = Deletable (Envelope v) ::: (Deletable (Trace v) ::: (Deletable (SubMap b v m) ::: (Query v m ::: ())))Source

Monoidal annotations which travel up the diagram tree, i.e. which are aggregated from component diagrams to the whole:

  • envelopes (see Diagrams.Core.Envelope). The envelopes are "deletable" meaning that at any point we can throw away the existing envelope and replace it with a new one; sometimes we want to consider a diagram as having a different envelope unrelated to its "natural" envelope.
  • traces (see Diagrams.Core.Trace), also deletable.
  • name/subdiagram associations (see Diagrams.Core.Names)
  • query functions (see Diagrams.Core.Query)

type DownAnnots v = (Split (Transformation v) :+: Style v) ::: (Name ::: ())Source

Monoidal annotations which travel down the diagram tree, i.e. which accumulate along each path to a leaf (and which can act on the upwards-travelling annotations):

transfToAnnot :: Transformation v -> DownAnnots vSource

Inject a transformation into a default downwards annotation value.

transfFromAnnot :: HasLinearMap v => DownAnnots v -> Transformation vSource

Extract the (total) transformation from a downwards annotation value.

Basic type definitions

data QDiaLeaf b v m Source

A leaf in a QDiagram tree is either a Prim, or a "delayed" QDiagram which expands to a real QDiagram once it learns the "final context" in which it will be rendered. For example, in order to decide how to draw an arrow, we must know the precise transformation applied to it (since the arrow head and tail are scale-invariant).

Constructors

PrimLeaf (Prim b v) 
DelayedLeaf (DownAnnots v -> QDiagram b v m)

The QDiagram produced by a DelayedLeaf function must already apply any non-frozen transformation in the given DownAnnots (that is, the non-frozen transformation will not be applied by the context). On the other hand, it must assume that any frozen transformation or attributes will be applied by the context.

Instances

Functor (QDiaLeaf b v) 
Wrapped (DUALTree (DownAnnots v) (UpAnnots b v m) () (QDiaLeaf b v m)) (DUALTree (DownAnnots v') (UpAnnots b' v' m') () (QDiaLeaf b' v' m')) (QDiagram b v m) (QDiagram b' v' m') 

withQDiaLeaf :: (Prim b v -> r) -> ((DownAnnots v -> QDiagram b v m) -> r) -> QDiaLeaf b v m -> rSource

newtype QDiagram b v m Source

The fundamental diagram type is represented by trees of primitives with various monoidal annotations. The Q in QDiagram stands for "Queriable", as distinguished from Diagram, a synonym for QDiagram with the query type specialized to Any.

Constructors

QD (DUALTree (DownAnnots v) (UpAnnots b v m) () (QDiaLeaf b v m)) 

Instances

Typeable3 QDiagram 
Functor (QDiagram b v) 
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Monoid (QDiagram b v m)

Diagrams form a monoid since each of their components do: the empty diagram has no primitives, an empty envelope, an empty trace, no named subdiagrams, and a constantly empty query function.

Diagrams compose by aligning their respective local origins. The new diagram has all the primitives and all the names from the two diagrams combined, and query functions are combined pointwise. The first diagram goes on top of the second. "On top of" probably only makes sense in vector spaces of dimension lower than 3, but in theory it could make sense for, say, 3-dimensional diagrams when viewed by 4-dimensional beings.

(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Semigroup (QDiagram b v m) 
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => HasOrigin (QDiagram b v m)

Every diagram has an intrinsic "local origin" which is the basis for all combining operations.

(HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Semigroup m) => Transformable (QDiagram b v m)

Diagrams can be transformed by transforming each of their components appropriately.

(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Qualifiable (QDiagram b v m)

Diagrams can be qualified so that all their named points can now be referred to using the qualification prefix.

(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => HasStyle (QDiagram b v m) 
(HasLinearMap v, VectorSpace v, Ord (Scalar v), InnerSpace v, Semigroup m, Fractional (Scalar v), Floating (Scalar v)) => Traced (QDiagram b v m) 
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => Enveloped (QDiagram b v m) 
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid' m) => Juxtaposable (QDiagram b v m) 
Wrapped (DUALTree (DownAnnots v) (UpAnnots b v m) () (QDiaLeaf b v m)) (DUALTree (DownAnnots v') (UpAnnots b' v' m') () (QDiaLeaf b' v' m')) (QDiagram b v m) (QDiagram b' v' m') 

type Diagram b v = QDiagram b v AnySource

The default sort of diagram is one where querying at a point simply tells you whether the diagram contains that point or not. Transforming a default diagram into one with a more interesting query can be done via the Functor instance of QDiagram b or the value function.

Operations on diagrams

Creating diagrams

mkQD :: Prim b v -> Envelope v -> Trace v -> SubMap b v m -> Query v m -> QDiagram b v mSource

Create a diagram from a single primitive, along with an envelope, trace, subdiagram map, and query function.

mkQD' :: QDiaLeaf b v m -> Envelope v -> Trace v -> SubMap b v m -> Query v m -> QDiagram b v mSource

Create a diagram from a generic QDiaLeaf, along with an envelope, trace, subdiagram map, and query function.

pointDiagram :: (Fractional (Scalar v), InnerSpace v) => Point v -> QDiagram b v mSource

Create a "point diagram", which has no content, no trace, an empty query, and a point envelope.

Extracting information

prims :: HasLinearMap v => QDiagram b v m -> [(Prim b v, (Split (Transformation v), Style v))]Source

Extract a list of primitives from a diagram, together with their associated transformations and styles.

envelope :: forall b v m. (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Monoid' m) => Lens' (QDiagram b v m) (Envelope v)Source

Get the envelope of a diagram.

trace :: (InnerSpace v, HasLinearMap v, OrderedField (Scalar v), Semigroup m) => Lens' (QDiagram b v m) (Trace v)Source

Get the trace of a diagram.

subMap :: (HasLinearMap v, InnerSpace v, Semigroup m, OrderedField (Scalar v)) => Lens' (QDiagram b v m) (SubMap b v m)Source

Get the subdiagram map (i.e. an association from names to subdiagrams) of a diagram.

names :: (HasLinearMap v, InnerSpace v, Semigroup m, OrderedField (Scalar v)) => QDiagram b v m -> [(Name, [Point v])]Source

Get a list of names of subdiagrams and their locations.

query :: Monoid m => QDiagram b v m -> Query v mSource

Get the query function associated with a diagram.

sample :: Monoid m => QDiagram b v m -> Point v -> mSource

Sample a diagram's query function at a given point.

value :: Monoid m => m -> QDiagram b v Any -> QDiagram b v mSource

Set the query value for True points in a diagram (i.e. points "inside" the diagram); False points will be set to mempty.

resetValue :: (Eq m, Monoid m) => QDiagram b v m -> QDiagram b v AnySource

Reset the query values of a diagram to True/False: any values equal to mempty are set to False; any other values are set to True.

clearValue :: QDiagram b v m -> QDiagram b v AnySource

Set all the query values of a diagram to False.

Combining diagrams

For many more ways of combining diagrams, see Diagrams.Combinators from the diagrams-lib package.

atop :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Semigroup m) => QDiagram b v m -> QDiagram b v m -> QDiagram b v mSource

A convenient synonym for mappend on diagrams, designed to be used infix (to help remember which diagram goes on top of which when combining them, namely, the first on top of the second).

Modifying diagrams

Names

nameSub :: (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => (QDiagram b v m -> Subdiagram b v m) -> n -> QDiagram b v m -> QDiagram b v mSource

Attach an atomic name to a certain subdiagram, computed from the given diagram.

lookupName :: (IsName n, HasLinearMap v, InnerSpace v, Semigroup m, OrderedField (Scalar v)) => n -> QDiagram b v m -> Maybe (Subdiagram b v m)Source

Lookup the most recent diagram associated with (some qualification of) the given name.

withName :: (IsName n, HasLinearMap v, InnerSpace v, Semigroup m, OrderedField (Scalar v)) => n -> (Subdiagram b v m -> QDiagram b v m -> QDiagram b v m) -> QDiagram b v m -> QDiagram b v mSource

Given a name and a diagram transformation indexed by a subdiagram, perform the transformation using the most recent subdiagram associated with (some qualification of) the name, or perform the identity transformation if the name does not exist.

withNameAll :: (IsName n, HasLinearMap v, InnerSpace v, Semigroup m, OrderedField (Scalar v)) => n -> ([Subdiagram b v m] -> QDiagram b v m -> QDiagram b v m) -> QDiagram b v m -> QDiagram b v mSource

Given a name and a diagram transformation indexed by a list of subdiagrams, perform the transformation using the collection of all such subdiagrams associated with (some qualification of) the given name.

withNames :: (IsName n, HasLinearMap v, InnerSpace v, Semigroup m, OrderedField (Scalar v)) => [n] -> ([Subdiagram b v m] -> QDiagram b v m -> QDiagram b v m) -> QDiagram b v m -> QDiagram b v mSource

Given a list of names and a diagram transformation indexed by a list of subdiagrams, perform the transformation using the list of most recent subdiagrams associated with (some qualification of) each name. Do nothing (the identity transformation) if any of the names do not exist.

localize :: forall b v m. (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => QDiagram b v m -> QDiagram b v mSource

"Localize" a diagram by hiding all the names, so they are no longer visible to the outside.

Other

freeze :: forall v b m. (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => QDiagram b v m -> QDiagram b v mSource

By default, diagram attributes are not affected by transformations. This means, for example, that lw 0.01 circle and scale 2 (lw 0.01 circle) will be drawn with lines of the same width, and scaleY 3 circle will be an ellipse drawn with a uniform line. Once a diagram is frozen, however, transformations do affect attributes, so, for example, scale 2 (freeze (lw 0.01 circle)) will be drawn with a line twice as thick as lw 0.01 circle, and scaleY 3 (freeze circle) will be drawn with a "stretched", variable-width line.

Another way of thinking about it is that pre-freeze, we are transforming the "abstract idea" of a diagram, and the transformed version is then drawn; when doing a freeze, we produce a concrete drawing of the diagram, and it is this visual representation itself which is acted upon by subsequent transformations.

setEnvelope :: forall b v m. (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Monoid' m) => Envelope v -> QDiagram b v m -> QDiagram b v mSource

Replace the envelope of a diagram.

setTrace :: forall b v m. (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Semigroup m) => Trace v -> QDiagram b v m -> QDiagram b v mSource

Replace the trace of a diagram.

Subdiagrams

data Subdiagram b v m Source

A Subdiagram represents a diagram embedded within the context of a larger diagram. Essentially, it consists of a diagram paired with any accumulated information from the larger context (transformations, attributes, etc.).

Constructors

Subdiagram (QDiagram b v m) (DownAnnots v) 

mkSubdiagram :: QDiagram b v m -> Subdiagram b v mSource

Turn a diagram into a subdiagram with no accumulated context.

getSub :: (HasLinearMap v, InnerSpace v, Floating (Scalar v), Ord (Scalar v), Semigroup m) => Subdiagram b v m -> QDiagram b v mSource

Turn a subdiagram into a normal diagram, including the enclosing context. Concretely, a subdiagram is a pair of (1) a diagram and (2) a "context" consisting of an extra transformation and attributes. getSub simply applies the transformation and attributes to the diagram to get the corresponding "top-level" diagram.

rawSub :: Subdiagram b v m -> QDiagram b v mSource

Extract the "raw" content of a subdiagram, by throwing away the context.

location :: HasLinearMap v => Subdiagram b v m -> Point vSource

Get the location of a subdiagram; that is, the location of its local origin with respect to the vector space of its parent diagram. In other words, the point where its local origin "ended up".

subPoint :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Semigroup m) => Point v -> Subdiagram b v mSource

Create a "point subdiagram", that is, a pointDiagram (with no content and a point envelope) treated as a subdiagram with local origin at the given point. Note this is not the same as mkSubdiagram . pointDiagram, which would result in a subdiagram with local origin at the parent origin, rather than at the given point.

Subdiagram maps

newtype SubMap b v m Source

A SubMap is a map associating names to subdiagrams. There can be multiple associations for any given name.

Constructors

SubMap (Map Name [Subdiagram b v m]) 

Instances

Action Name (SubMap b v m)

A name acts on a name map by qualifying every name in it.

Functor (SubMap b v) 
Wrapped (Map Name [Subdiagram b v m]) (Map Name [Subdiagram b v m']) (SubMap b v m) (SubMap b v m') 
Monoid (SubMap b v m)

SubMaps form a monoid with the empty map as the identity, and map union as the binary operation. No information is ever lost: if two maps have the same name in their domain, the resulting map will associate that name to the concatenation of the information associated with that name.

Semigroup (SubMap b v m) 
(OrderedField (Scalar v), InnerSpace v, HasLinearMap v) => HasOrigin (SubMap b v m) 
(InnerSpace v, Floating (Scalar v), HasLinearMap v) => Transformable (SubMap b v m) 
Qualifiable (SubMap b v m)

SubMaps are qualifiable: if ns is a SubMap, then a |> ns is the same SubMap except with every name qualified by a.

Wrapped (DUALTree (DownAnnots v) (UpAnnots b v m) () (QDiaLeaf b v m)) (DUALTree (DownAnnots v') (UpAnnots b' v' m') () (QDiaLeaf b' v' m')) (QDiagram b v m) (QDiagram b' v' m') 

fromNames :: IsName a => [(a, Subdiagram b v m)] -> SubMap b v mSource

Construct a SubMap from a list of associations between names and subdiagrams.

rememberAs :: IsName a => a -> QDiagram b v m -> SubMap b v m -> SubMap b v mSource

Add a name/diagram association to a submap.

lookupSub :: IsName n => n -> SubMap b v m -> Maybe [Subdiagram b v m]Source

Look for the given name in a name map, returning a list of subdiagrams associated with that name. If no names match the given name exactly, return all the subdiagrams associated with names of which the given name is a suffix.

Primtives

Ultimately, every diagram is essentially a list of primitives, basic building blocks which can be rendered by backends. However, not every backend must be able to render every type of primitive; the collection of primitives a given backend knows how to render is determined by instances of Renderable.

data Prim b v whereSource

A value of type Prim b v is an opaque (existentially quantified) primitive which backend b knows how to render in vector space v.

Constructors

Prim :: (IsPrim p, Renderable p b) => p -> Prim b (V p) 

Instances

HasLinearMap v => Transformable (Prim b v)

The Transformable instance for Prim just pushes calls to transform down through the Prim constructor.

HasLinearMap v => IsPrim (Prim b v) 
HasLinearMap v => Renderable (Prim b v) b

The Renderable instance for Prim just pushes calls to render down through the Prim constructor.

class Transformable p => IsPrim p whereSource

A type class for primitive things which know how to handle being transformed by both a normal transformation and a "frozen" transformation. The default implementation simply applies both. At the moment, ScaleInv is the only type with a non-default instance of IsPrim.

Instances

HasLinearMap v => IsPrim (Prim b v) 

nullPrim :: (HasLinearMap v, Monoid (Render b v)) => Prim b vSource

The null primitive, which every backend can render by doing nothing.

Backends

class (HasLinearMap v, Monoid (Render b v)) => Backend b v whereSource

Abstract diagrams are rendered to particular formats by backends. Each backend/vector space combination must be an instance of the Backend class. A minimal complete definition consists of the three associated types, an implementation for doRender, and one of either withStyle or renderData.

Associated Types

data Render b v :: *Source

The type of rendering operations used by this backend, which must be a monoid. For example, if Render b v = M () for some monad M, a monoid instance can be made with mempty = return () and mappend = (>>).

type Result b v :: *Source

The result of running/interpreting a rendering operation.

data Options b v :: *Source

Backend-specific rendering options.

Methods

withStyleSource

Arguments

:: b

Backend token (needed only for type inference)

-> Style v

Style to use

-> Transformation v

"Frozen" transformation; line width and other similar "scale invariant" attributes should be affected by this transformation. In the case of 2D, some backends may not support stroking in the context of an arbitrary transformation; such backends can instead use the avgScale function from Diagrams.TwoD.Transform (from the diagrams-lib package).

-> Render b v

Rendering operation to run

-> Render b v

Rendering operation using the style locally

Perform a rendering operation with a local style. The default implementation does nothing, and must be overridden by backends that do not override renderData.

doRenderSource

Arguments

:: b

Backend token (needed only for type inference)

-> Options b v

Backend-specific collection of rendering options

-> Render b v

Rendering operation to perform

-> Result b v

Output of the rendering operation

doRender is used to interpret rendering operations.

adjustDia :: Monoid' m => b -> Options b v -> QDiagram b v m -> (Options b v, QDiagram b v m)Source

adjustDia allows the backend to make adjustments to the final diagram (e.g. to adjust the size based on the options) before rendering it. It can also make adjustments to the options record, usually to fill in incompletely specified size information. A default implementation is provided which makes no adjustments. See the diagrams-lib package for other useful implementations.

renderDia :: (InnerSpace v, OrderedField (Scalar v), Monoid' m) => b -> Options b v -> QDiagram b v m -> Result b vSource

renderData :: Monoid' m => b -> QDiagram b v m -> Render b vSource

Backends may override renderData to gain more control over the way that rendering happens. A typical implementation might be something like

 renderData = renderRTree . toRTree

where renderRTree :: RTree b v () -> Render b v is implemented by the backend (with appropriate types filled in for b and v), and toRTree is from Diagrams.Core.Compile.

Instances

class Backend b v => MultiBackend b v whereSource

A class for backends which support rendering multiple diagrams, e.g. to a multi-page pdf or something similar.

Methods

renderDias :: (InnerSpace v, OrderedField (Scalar v), Monoid' m) => b -> Options b v -> [QDiagram b v m] -> Result b vSource

Render multiple diagrams at once.

data DNode b v a Source

Constructors

DStyle (Style v) 
DTransform (Split (Transformation v)) 
DAnnot a 
DDelay

DDelay marks a point where a delayed subtree was expanded. Such subtrees already take all non-frozen transforms above them into account, so when later processing the tree, upon encountering a DDelay node we must drop any accumulated non-frozen transformation.

DPrim (Prim b v) 
DEmpty 

type DTree b v a = Tree (DNode b v a)Source

A DTree is a raw tree representation of a QDiagram, with all the u-annotations removed. It is used as an intermediate type by diagrams-core; backends should not need to make use of it. Instead, backends can make use of RTree, which DTree gets compiled and optimized to.

data RNode b v a Source

Constructors

RStyle (Style v)

A style node.

RFrozenTr (Transformation v)

A "frozen" transformation, i.e. one which was applied after a call to freeze. It applies to everything below it in the tree. Note that line width and other similar "scale invariant" attributes should be affected by this transformation. In the case of 2D, some backends may not support stroking in the context of an arbitrary transformation; such backends can instead use the avgScale function from Diagrams.TwoD.Transform (from the diagrams-lib package).

RAnnot a 
RPrim (Transformation v) (Prim b v)

A primitive, along with the (non-frozen) transformation which applies to it.

REmpty 

type RTree b v a = Tree (RNode b v a)Source

An RTree is a compiled and optimized representation of a QDiagram, which can be used by backends. They have several invariants which backends may rely upon:

  • All non-frozen transformations have been pushed all the way to the leaves.
  • RPrim nodes never have any children.

Null backend

data NullBackend Source

A null backend which does no actual rendering. It is provided mainly for convenience in situations where you must give a diagram a concrete, monomorphic type, but don't actually care which one. See D for more explanation and examples.

It is courteous, when defining a new primitive P, to make an instance

 instance Renderable P NullBackend where
   render _ _ = mempty

This ensures that the trick with D annotations can be used for diagrams containing your primitive.

type D v = Diagram NullBackend vSource

The D type is provided for convenience in situations where you must give a diagram a concrete, monomorphic type, but don't care which one. Such situations arise when you pass a diagram to a function which is polymorphic in its input but monomorphic in its output, such as width, height, phantom, or names. Such functions compute some property of the diagram, or use it to accomplish some other purpose, but do not result in the diagram being rendered. If the diagram does not have a monomorphic type, GHC complains that it cannot determine the diagram's type.

For example, here is the error we get if we try to compute the width of an image (this example requires diagrams-lib):

 ghci> width (image "foo.png" 200 200)

 <interactive>:8:8:
     No instance for (Renderable Diagrams.TwoD.Image.Image b0)
       arising from a use of `image'
     Possible fix:
       add an instance declaration for
       (Renderable Diagrams.TwoD.Image.Image b0)
     In the first argument of `width', namely
       `(image "foo.png" 200 200)'
     In the expression: width (image "foo.png" 200 200)
     In an equation for `it': it = width (image "foo.png" 200 200)

GHC complains that there is no instance for Renderable Image b0; what is really going on is that it does not have enough information to decide what backend to use (hence the uninstantiated b0). This is annoying because we know that the choice of backend cannot possibly affect the width of the image (it's 200! it's right there in the code!); but there is no way for GHC to know that.

The solution is to annotate the call to image with the type D R2, like so:

 ghci> width (image "foo.png" 200 200 :: D R2)
 200.00000000000006

(It turns out the width wasn't 200 after all...)

As another example, here is the error we get if we try to compute the width of a radius-1 circle:

 ghci> width (circle 1)

 <interactive>:4:1:
     Couldn't match type `V a0' with `R2'
     In the expression: width (circle 1)
     In an equation for `it': it = width (circle 1)

There's even more ambiguity here. Whereas image always returns a Diagram, the circle function can produce any PathLike type, and the width function can consume any Enveloped type, so GHC has no idea what type to pick to go in the middle. However, the solution is the same:

 ghci> width (circle 1 :: D R2)
 1.9999999999999998

Renderable

class Transformable t => Renderable t b whereSource

The Renderable type class connects backends to primitives which they know how to render.

Methods

render :: b -> t -> Render b (V t)Source

Given a token representing the backend and a transformable object, render it in the appropriate rendering context.

Instances

HasLinearMap v => Renderable (Prim b v) b

The Renderable instance for Prim just pushes calls to render down through the Prim constructor.