diagrams-core-0.4: Core libraries for diagrams EDSL

Maintainerdiagrams-discuss@googlegroups.com

Graphics.Rendering.Diagrams

Contents

Description

The core library of primitives forming the basis of an embedded domain-specific language for describing and rendering diagrams. Normal users of the diagrams library should almost never need to import anything from this package directly; instead, import modules (especially Diagrams.Prelude) from the diagrams-lib package, which re-exports most things of value to users.

For most library code needing access to core internals, it should be sufficient to import this module, which simply re-exports useful functionality from other modules in the core library. Library writers needing finer-grained access or functionality may occasionally find it useful to directly import one of the constituent core modules.

Synopsis

Associated vector spaces

type family V a :: *Source

Many sorts of objects have an associated vector space in which they live. The type function V maps from objects to their associated vector space.

Points

newtype Point v Source

Point is a newtype wrapper around vectors that we wish to treat as points, so we don't get them mixed up. The distinction is important: translations affect points, but leave vectors unchanged. Points are instances of the AffineSpace class from Data.AffineSpace.

Constructors

P v 

Instances

origin :: AdditiveGroup v => Point vSource

The origin of the vector space v.

(*.) :: VectorSpace v => Scalar v -> Point v -> Point vSource

Scale a point by a scalar.

Vectors

withLength :: (InnerSpace v, Floating (Scalar v)) => Scalar v -> v -> vSource

Produce a vector with the specified length in the same direction as the given vector.

Transformations

Invertible linear transformations

data u :-: v Source

(v1 :-: v2) is a linear map paired with its inverse.

Instances

HasLinearMap v => Monoid (:-: v v)

Invertible linear maps from a vector space to itself form a monoid under composition.

(<->) :: (HasLinearMap u, HasLinearMap v) => (u -> v) -> (v -> u) -> u :-: vSource

Create an invertible linear map from two functions which are assumed to be linear inverses.

linv :: (u :-: v) -> v :-: uSource

Invert a linear map.

lapp :: (VectorSpace v, Scalar u ~ Scalar v, HasLinearMap u) => (u :-: v) -> u -> vSource

Apply a linear map to a vector.

General transformations

data Transformation v Source

General (affine) transformations, represented by an invertible linear map, its transpose, and a vector representing a translation component.

Instances

HasLinearMap v => Monoid (Transformation v)

Transformations are closed under composition; t1 t2 is the transformation which performs first t2, then t1.

HasLinearMap v => HasOrigin (Transformation v) 
HasLinearMap v => Transformable (Transformation v) 
(v ~ V a, HasLinearMap v, Transformable a) => Action (Transformation v) a

Transformations can act on transformable things.

inv :: HasLinearMap v => Transformation v -> Transformation vSource

Invert a transformation.

transp :: Transformation v -> v :-: vSource

Get the transpose of a transformation (ignoring the translation component).

transl :: Transformation v -> vSource

Get the translational component of a transformation.

apply :: HasLinearMap v => Transformation v -> v -> vSource

Apply a transformation to a vector. Note that any translational component of the transformation will not affect the vector, since vectors are invariant under translation.

papply :: HasLinearMap v => Transformation v -> Point v -> Point vSource

Apply a transformation to a point.

fromLinear :: AdditiveGroup v => (v :-: v) -> (v :-: v) -> Transformation vSource

Create a general affine transformation from an invertible linear transformation and its transpose. The translational component is assumed to be zero.

Some specific transformations

translation :: HasLinearMap v => v -> Transformation vSource

Create a translation.

translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> tSource

Translate by a vector.

moveTo :: HasOrigin t => Point (V t) -> t -> tSource

Translate the object by the translation that sends the origin to the given point. Note that this is dual to moveOriginTo, i.e. we should have

 moveTo (origin .^+ v) === moveOriginTo (origin .^- v)

For types which are also Transformable, this is essentially the same as translate, i.e.

 moveTo (origin .^+ v) === translate v

place :: HasOrigin t => t -> Point (V t) -> tSource

A flipped variant of moveTo, provided for convenience. Useful when writing a function which takes a point as an argument, such as when using withName and friends.

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

Create a uniform scaling transformation.

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

Scale uniformly in every dimension by the given scalar.

The Transformable class

class HasLinearMap (V t) => Transformable t whereSource

Type class for things t which can be transformed.

Methods

transform :: Transformation (V t) -> t -> tSource

Apply a transformation to an object.

Instances

Transformable t => Transformable [t] 
(Transformable t, Ord t) => Transformable (Set t) 
HasLinearMap v => Transformable (Point v) 
Transformable m => Transformable (Deletable m) 
Transformable m => Transformable (Forgetful m) 
Transformable t => Transformable (TransInv t) 
HasLinearMap v => Transformable (Transformation v) 
(HasLinearMap v, InnerSpace v, Floating (Scalar v), AdditiveGroup (Scalar v)) => Transformable (Bounds v) 
(AdditiveGroup (Scalar v), InnerSpace v, Floating (Scalar v), HasLinearMap v) => Transformable (NameMap v) 
HasLinearMap v => Transformable (Style v) 
HasLinearMap v => Transformable (Attribute v) 
HasLinearMap v => Transformable (NullPrim v) 
Transformable t => Transformable (Map k t) 
HasLinearMap v => Transformable (Query v m) 
HasLinearMap v => Transformable (Prim b v)

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

(HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Monoid m) => Transformable (AnnDiagram b v m)

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

Translational invariance

newtype TransInv t Source

TransInv is a wrapper which makes a transformable type translationally invariant; the translational component of transformations will no longer affect things wrapped in TransInv.

Constructors

TransInv 

Fields

unTransInv :: t
 

Names

data AName Source

Atomic names. AName is just an existential wrapper around things which are Typeable, Ord and Show.

data Name Source

A (qualified) name is a (possibly empty) sequence of atomic names.

Instances

Eq Name 
Ord Name 
Show Name 
Typeable Name 
Monoid Name 
Qualifiable Name

Of course, names can be qualified using (.>).

IsName Name 
Action Name a

Names don't act on anything else.

Action Name (NameMap v)

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

class (Typeable a, Ord a, Show a) => IsName a whereSource

Class for those types which can be used as names. They must support Typeable (to facilitate extracting them from existential wrappers), Ord (for comparison and efficient storage) and Show.

Methods

toName :: a -> NameSource

class Qualifiable q whereSource

Instances of Qualifiable are things which can be qualified by prefixing them with a name.

Methods

(|>) :: IsName a => a -> q -> qSource

Qualify with the given name.

Instances

Qualifiable Name

Of course, names can be qualified using (.>).

Qualifiable (NameMap v)

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

(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => Qualifiable (AnnDiagram b v m)

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

(.>) :: (IsName a1, IsName a2) => a1 -> a2 -> NameSource

Convenient operator for writing qualified names with atomic components of different types. Instead of writing toName a1 <> toName a2 <> toName a3 you can just write a1 .> a2 .> a3.

data NameMap v Source

A NameMap is a map associating names to pairs of points (local origins) and bounding functions. There can be multiple (point, bounding function) pairs associated with each name.

Instances

Action Name (NameMap v)

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

Show v => Show (NameMap v) 
Monoid (NameMap v)

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

(AdditiveGroup (Scalar v), Fractional (Scalar v), InnerSpace v) => HasOrigin (NameMap v) 
(AdditiveGroup (Scalar v), InnerSpace v, Floating (Scalar v), HasLinearMap v) => Transformable (NameMap v) 
Qualifiable (NameMap v)

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

fromNames :: (AdditiveGroup (Scalar v), Ord (Scalar v), IsName a) => [(a, Point v)] -> NameMap vSource

Construct a NameMap from a list of (name, point) pairs. The bounding functions will be empty.

fromNamesB :: IsName a => [(a, (Point v, Bounds v))] -> NameMap vSource

Construct a NameMap from a list of associations between names and (point, bounds) pairs.

rememberAs :: IsName a => a -> Point v -> Bounds v -> NameMap v -> NameMap vSource

Give a name to a point and bounding function.

lookupN :: IsName n => n -> NameMap v -> Maybe [(Point v, Bounds v)]Source

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

Attributes and styles

class (Typeable a, Semigroup a) => AttributeClass a Source

Every attribute must be an instance of AttributeClass, which simply guarantees Typeable and Semigroup constraints. The Semigroup instance for an attribute determines how it will combine with other attributes of the same type.

data Attribute v Source

An existential wrapper type to hold attributes. Some attributes are affected by transformations and some are not.

Instances

Semigroup (Attribute v)

Attributes form a semigroup, where the semigroup operation simply returns the right-hand attribute when the types do not match, and otherwise uses the semigroup operation specific to the (matching) types.

HasLinearMap v => Transformable (Attribute v) 

mkAttr :: AttributeClass a => a -> Attribute vSource

Wrap up an attribute.

mkTAttr :: (AttributeClass a, Transformable a, V a ~ v) => a -> Attribute vSource

Wrap up a transformable attribute.

unwrapAttr :: AttributeClass a => Attribute v -> Maybe aSource

Unwrap an unknown Attribute type, performing a dynamic (but safe) check on the type of the result. If the required type matches the type of the attribute, the attribute value is returned wrapped in Just; if the types do not match, Nothing is returned.

data Style v Source

A Style is a heterogeneous collection of attributes, containing at most one attribute of any given type.

Instances

Monoid (Style v)

The empty style contains no attributes; composition of styles is a union of attributes; if the two styles have attributes of the same type they are combined according to their semigroup structure.

HasLinearMap v => Transformable (Style v) 
HasStyle (Style v) 
Action (Style v) m

Styles have no action on other monoids.

class HasStyle a whereSource

Type class for things which have a style.

Methods

applyStyle :: Style (V a) -> a -> aSource

Apply a style by combining it (on the left) with the existing style.

Instances

getAttr :: forall a v. AttributeClass a => Style v -> Maybe aSource

Extract an attribute from a style of a particular type. If the style contains an attribute of the requested type, it will be returned wrapped in Just; otherwise, Nothing is returned.

combineAttr :: AttributeClass a => a -> Style v -> Style vSource

Add a new attribute to a style that does not already contain an attribute of this type, or combine it on the left with an existing attribute.

applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> dSource

Apply an attribute to an instance of HasStyle (such as a diagram or a style). If the object already has an attribute of the same type, the new attribute is combined on the left with the existing attribute, according to their semigroup structure.

applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, HasStyle d) => a -> d -> dSource

Apply a transformable attribute to an instance of HasStyle (such as a diagram or a style). If the object already has an attribute of the same type, the new attribute is combined on the left with the existing attribute, according to their semigroup structure.

Bounding regions

newtype Bounds v Source

Every diagram comes equipped with a bounding function. Intuitively, the bounding function for a diagram tells us the minimum distance we have to go in a given direction to get to a (hyper)plane entirely containing the diagram on one side of it. Formally, given a vector v, it returns a scalar s such that

  • for every vector u with its endpoint inside the diagram, if the projection of u onto v is s' *^ v, then s' <= s.
  • s is the smallest such scalar.

This could probably be expressed in terms of a Galois connection; this is left as an exercise for the reader.

Essentially, bounding functions are a functional representation of (a conservative approximation to) convex bounding regions. The idea for this representation came from Sebastian Setzer; see http://byorgey.wordpress.com/2009/10/28/collecting-attributes/#comment-2030.

Constructors

Bounds 

Fields

appBounds :: v -> Scalar v
 

Instances

Show (Bounds v) 
(Ord (Scalar v), AdditiveGroup (Scalar v)) => Monoid (Bounds v)

Bounding functions form a monoid, with the constantly zero function (i.e. the empty region) as the identity, and pointwise maximum as composition. Hence, if b1 is the bounding function for diagram d1, and b2 is the bounding function for d2, then b1 `mappend` b2 is the bounding function for d1 `atop` d2.

(InnerSpace v, AdditiveGroup (Scalar v), Fractional (Scalar v)) => HasOrigin (Bounds v)

The local origin of a bounding function is the point with respect to which bounding queries are made, i.e. the point from which the input vectors are taken to originate.

(HasLinearMap v, InnerSpace v, Floating (Scalar v), AdditiveGroup (Scalar v)) => Transformable (Bounds v) 
(InnerSpace v, OrderedField (Scalar v)) => Boundable (Bounds v) 

class (InnerSpace (V b), OrderedField (Scalar (V b))) => Boundable b whereSource

Boundable abstracts over things which can be bounded.

Methods

getBounds :: b -> Bounds (V b)Source

Given a boundable object, compute a functional bounding region for it. For types with an intrinsic notion of "local origin", the bounding function will be based there. Other types (e.g. Trail) may have some other default reference point at which the bounding function will be based; their instances should document what it is.

boundaryV :: Boundable a => V a -> a -> V aSource

Compute the vector from the local origin to a separating hyperplane in the given direction.

boundary :: Boundable a => V a -> a -> Point (V a)Source

Compute the point on the boundary in the given direction. Caution: this point is only valid in the local vector space of the Boundable object. If you want to compute boundary points of things which are subparts of a larger diagram (and hence embedded within a different vector space), you must use boundaryFrom instead.

boundaryFrom :: Boundable a => Point (V a) -> V a -> a -> Point (V a)Source

boundaryFrom o v a computes the point along the boundary of a in the direction of v, assuming that a's local origin is located at the point o of the vector space we care about.

diameter :: Boundable a => V a -> a -> Scalar (V a)Source

Compute the diameter of a boundable object along a particular vector.

radius :: Boundable a => V a -> a -> Scalar (V a)Source

Compute the radius (1/2 the diameter) of a boundable object along a particular vector.

Things with local origins

class VectorSpace (V t) => HasOrigin t whereSource

Class of types which have an intrinsic notion of a "local origin", i.e. things which are not invariant under translation, and which allow the origin to be moved.

One might wonder why not just use Transformable instead of having a separate class for HasOrigin; indeed, for types which are instances of both we should have the identity

 moveOriginTo (origin .^+ v) === translate (negateV v)

The reason is that some things (e.g. vectors, Trails) are transformable but are translationally invariant, i.e. have no origin.

Methods

moveOriginTo :: Point (V t) -> t -> tSource

Move the local origin to another point.

Note that this function is in some sense dual to translate (for types which are also Transformable); moving the origin itself while leaving the object "fixed" is dual to fixing the origin and translating the diagram.

Instances

HasOrigin a => HasOrigin [a] 
VectorSpace v => HasOrigin (Point v) 
VectorSpace (V t) => HasOrigin (TransInv t) 
HasLinearMap v => HasOrigin (Transformation v) 
(InnerSpace v, AdditiveGroup (Scalar v), Fractional (Scalar v)) => HasOrigin (Bounds v)

The local origin of a bounding function is the point with respect to which bounding queries are made, i.e. the point from which the input vectors are taken to originate.

(AdditiveGroup (Scalar v), Fractional (Scalar v), InnerSpace v) => HasOrigin (NameMap v) 
VectorSpace v => HasOrigin (Query v m) 
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => HasOrigin (AnnDiagram b v m)

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

moveOriginBy :: HasOrigin t => V t -> t -> tSource

Move the local origin by a relative vector.

Queries

newtype Query v m Source

A query is a function that maps points in a vector space to values in some monoid. Queries naturally form a monoid, with two queries being combined pointwise.

The idea for annotating diagrams with monoidal queries came from the graphics-drawingcombinators package, http://hackage.haskell.org/package/graphics-drawingcombinators.

Constructors

Query 

Fields

runQuery :: Point v -> m
 

Instances

Primtives

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 :: Renderable t b => t -> Prim b (V t) 

Instances

HasLinearMap v => Transformable (Prim b v)

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

HasLinearMap v => Renderable (Prim b v) b

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

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

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

Diagrams

data AnnDiagram b v m Source

The fundamental diagram type is represented by trees of primitives with various monoidal annotations.

Instances

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

Diagrams form a monoid since each of their components do: the empty diagram has no primitives, a constantly zero bounding function, no named points, 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), Monoid m) => HasOrigin (AnnDiagram 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, Monoid m) => Transformable (AnnDiagram b v m)

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

(HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Boundable (AnnDiagram b v m) 
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => Qualifiable (AnnDiagram 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), Monoid m) => HasStyle (AnnDiagram b v m) 

mkAD :: Prim b v -> Bounds v -> NameMap v -> Query v m -> AnnDiagram b v mSource

Create a diagram from a single primitive, along with a bounding region, name map, and query function.

type Diagram b v = AnnDiagram b v AnySource

The default sort of diagram is one where sampling at a point simply tells you whether that point is occupied or not. Transforming a default diagram into one with more interesting annotations can be done via the Functor instance of AnnDiagram b.

prims :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => AnnDiagram 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.

bounds :: (OrderedField (Scalar v), InnerSpace v, HasLinearMap v) => AnnDiagram b v m -> Bounds vSource

Get the bounds of a diagram.

names :: (AdditiveGroup (Scalar v), Floating (Scalar v), InnerSpace v, HasLinearMap v) => AnnDiagram b v m -> NameMap vSource

Get the name map of a diagram.

query :: (HasLinearMap v, Monoid m) => AnnDiagram b v m -> Query v mSource

Get the query function associated with a diagram.

sample :: (HasLinearMap v, Monoid m) => AnnDiagram b v m -> Point v -> mSource

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

value :: Monoid m => m -> AnnDiagram b v Any -> AnnDiagram 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) => AnnDiagram b v m -> AnnDiagram 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 :: AnnDiagram b v m -> AnnDiagram b v AnySource

Set all the query values of a diagram to False.

named :: forall v b n m. (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => n -> AnnDiagram b v m -> AnnDiagram b v mSource

Attach an atomic name to (the local origin of) a diagram.

namePoint :: forall v b n m. (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => (AnnDiagram b v m -> (Point v, Bounds v)) -> n -> AnnDiagram b v m -> AnnDiagram b v mSource

Attach an atomic name to a certain point and bounding function, computed from the given diagram.

withName :: (IsName n, AdditiveGroup (Scalar v), Floating (Scalar v), InnerSpace v, HasLinearMap v) => n -> ((Point v, Bounds v) -> AnnDiagram b v m -> AnnDiagram b v m) -> AnnDiagram b v m -> AnnDiagram b v mSource

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

withNameAll :: (IsName n, AdditiveGroup (Scalar v), Floating (Scalar v), InnerSpace v, HasLinearMap v) => n -> ([(Point v, Bounds v)] -> AnnDiagram b v m -> AnnDiagram b v m) -> AnnDiagram b v m -> AnnDiagram b v mSource

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

withNames :: (IsName n, AdditiveGroup (Scalar v), Floating (Scalar v), InnerSpace v, HasLinearMap v) => [n] -> ([(Point v, Bounds v)] -> AnnDiagram b v m -> AnnDiagram b v m) -> AnnDiagram b v m -> AnnDiagram b v mSource

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

freeze :: forall v b m. (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => AnnDiagram b v m -> AnnDiagram 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.

setBounds :: forall b v m. (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Monoid m) => Bounds v -> AnnDiagram b v m -> AnnDiagram b v mSource

Replace the bounds of a diagram.

atop :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Monoid m) => AnnDiagram b v m -> AnnDiagram b v m -> AnnDiagram 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).

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 and implementations for withStyle and doRender.

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

Transformation to be applied to the style

-> Render b v

Rendering operation to run

-> Render b v

Rendering operation using the style locally

Perform a rendering operation with a local style.

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 -> AnnDiagram b v m -> AnnDiagram b v mSource

adjustDia allows the backend to make adjustments to the final diagram (e.g. to adjust the size based on the options) before rendering it. 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 -> AnnDiagram b v m -> Result b vSource

Render a diagram. This has a default implementation in terms of adjustDia, withStyle, doRender, and the render operation from the Renderable class (first adjustDia is used, then withStyle and render are used to render each primitive, the resulting operations are combined with mconcat, and the final operation run with doRender) but backends may override it if desired.

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 :: b -> Options b v -> [AnnDiagram b v m] -> Result b vSource

Render multiple diagrams at once.

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, Monoid (Render b v)) => Renderable (NullPrim v) b 
HasLinearMap v => Renderable (Prim b v) b

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

Convenience classes

class (HasBasis v, HasTrie (Basis v), VectorSpace v) => HasLinearMap v Source

HasLinearMap is a poor man's class constraint synonym, just to help shorten some of the ridiculously long constraint sets.

Instances

class (Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s Source

When dealing with bounding regions we often want scalars to be an ordered field (i.e. support all four arithmetic operations and be totally ordered) so we introduce this class as a convenient shorthand.

Instances