Maintainer | diagrams-discuss@googlegroups.com |
---|
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.
- type family V a :: *
- newtype Point v = P v
- origin :: AdditiveGroup v => Point v
- (*.) :: VectorSpace v => Scalar v -> Point v -> Point v
- withLength :: (InnerSpace v, Floating (Scalar v)) => Scalar v -> v -> v
- data u :-: v
- (<->) :: (HasLinearMap u, HasLinearMap v) => (u -> v) -> (v -> u) -> u :-: v
- linv :: (u :-: v) -> v :-: u
- lapp :: (VectorSpace v, Scalar u ~ Scalar v, HasLinearMap u) => (u :-: v) -> u -> v
- data Transformation v
- inv :: HasLinearMap v => Transformation v -> Transformation v
- transp :: Transformation v -> v :-: v
- transl :: Transformation v -> v
- apply :: HasLinearMap v => Transformation v -> v -> v
- papply :: HasLinearMap v => Transformation v -> Point v -> Point v
- fromLinear :: AdditiveGroup v => (v :-: v) -> (v :-: v) -> Transformation v
- translation :: HasLinearMap v => v -> Transformation v
- translate :: (Transformable t, HasLinearMap (V t)) => V t -> t -> t
- moveTo :: HasOrigin t => Point (V t) -> t -> t
- scaling :: (HasLinearMap v, Fractional (Scalar v)) => Scalar v -> Transformation v
- scale :: (Transformable t, Fractional (Scalar (V t))) => Scalar (V t) -> t -> t
- class HasLinearMap (V t) => Transformable t where
- transform :: Transformation (V t) -> t -> t
- data Name
- class IsName n where
- class Qualifiable a where
- (||>) :: (IsName n, IsName m) => n -> m -> Name
- data NameMap v
- fromNames :: IsName n => [(n, Point v)] -> NameMap v
- rememberAs :: Name -> Point v -> NameMap v -> NameMap v
- lookupN :: IsName n => n -> NameMap v -> Maybe [Point v]
- class (Typeable a, Semigroup a) => AttributeClass a
- data Attribute v
- mkAttr :: AttributeClass a => a -> Attribute v
- mkTAttr :: (AttributeClass a, Transformable a, V a ~ v) => a -> Attribute v
- unwrapAttr :: AttributeClass a => Attribute v -> Maybe a
- data Style v
- class HasStyle a where
- applyStyle :: Style (V a) -> a -> a
- getAttr :: forall a v. AttributeClass a => Style v -> Maybe a
- combineAttr :: AttributeClass a => a -> Style v -> Style v
- applyAttr :: (AttributeClass a, HasStyle d) => a -> d -> d
- applyTAttr :: (AttributeClass a, Transformable a, V a ~ V d, HasStyle d) => a -> d -> d
- newtype Bounds v = Bounds {}
- class (InnerSpace (V b), OrderedField (Scalar (V b))) => Boundable b where
- boundary :: Boundable a => V a -> a -> Point (V a)
- diameter :: Boundable a => V a -> a -> Scalar (V a)
- radius :: Boundable a => V a -> a -> Scalar (V a)
- class VectorSpace (V t) => HasOrigin t where
- moveOriginTo :: Point (V t) -> t -> t
- moveOriginBy :: HasOrigin t => V t -> t -> t
- newtype Query v m = Query {}
- data Prim b v where
- Prim :: Renderable t b => t -> Prim b (V t)
- nullPrim :: (HasLinearMap v, Monoid (Render b v)) => Prim b v
- data AnnDiagram b v m
- mkAD :: Prim b v -> Bounds v -> NameMap v -> Query v m -> AnnDiagram b v m
- type Diagram b v = AnnDiagram b v Any
- prims :: (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => AnnDiagram b v m -> [(Prim b v, (Split (Transformation v), Style v))]
- bounds :: (OrderedField (Scalar v), InnerSpace v, HasLinearMap v) => AnnDiagram b v m -> Bounds v
- names :: HasLinearMap v => AnnDiagram b v m -> NameMap v
- query :: (HasLinearMap v, Monoid m) => AnnDiagram b v m -> Query v m
- sample :: (HasLinearMap v, Monoid m) => AnnDiagram b v m -> Point v -> m
- 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 m
- namePoint :: forall v b n m. (IsName n, HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => (AnnDiagram b v m -> Point v) -> n -> AnnDiagram b v m -> AnnDiagram b v m
- withName :: HasLinearMap v => Name -> (Point v -> AnnDiagram b v m -> AnnDiagram b v m) -> AnnDiagram b v m -> AnnDiagram b v m
- freeze :: forall v b m. (HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => AnnDiagram b v m -> AnnDiagram b v m
- setBounds :: (OrderedField (Scalar v), InnerSpace v, HasLinearMap v, Monoid m) => Bounds v -> AnnDiagram b v m -> AnnDiagram b v m
- atop :: (HasLinearMap v, OrderedField (Scalar v), InnerSpace v, Monoid m) => AnnDiagram b v m -> AnnDiagram b v m -> AnnDiagram b v m
- class (HasLinearMap v, Monoid (Render b v)) => Backend b v where
- data Render b v :: *
- type Result b v :: *
- data Options b v :: *
- withStyle :: b -> Style v -> Transformation v -> Render b v -> Render b v
- doRender :: b -> Options b v -> Render b v -> Result b v
- adjustDia :: Monoid m => b -> Options b v -> AnnDiagram b v m -> AnnDiagram b v m
- renderDia :: (InnerSpace v, OrderedField (Scalar v), Monoid m) => b -> Options b v -> AnnDiagram b v m -> Result b v
- class Backend b v => MultiBackend b v where
- renderDias :: b -> Options b v -> [AnnDiagram b v m] -> Result b v
- class Transformable t => Renderable t b where
- class (HasBasis v, HasTrie (Basis v), VectorSpace v) => HasLinearMap v
- class (Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s
Associated vector spaces
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
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.
P v |
origin :: AdditiveGroup v => Point vSource
The origin of the vector space v
.
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
(v1 :-: v2)
is a linear map paired with its inverse.
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.
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.
HasLinearMap v => Monoid (Transformation v) | Transformations are closed under composition; |
(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
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.
transform :: Transformation (V t) -> t -> tSource
Apply a transformation to an object.
Transformable t => Transformable [t] | |
(Transformable t, Ord t) => Transformable (Set t) | |
HasLinearMap v => Transformable (Point v) | |
Transformable m => Transformable (Forgetful m) | |
HasLinearMap v => Transformable (NameMap v) | |
(HasLinearMap v, InnerSpace v, Floating (Scalar v), AdditiveGroup (Scalar v)) => Transformable (Bounds 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 |
(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. |
Names
A (qualified) name is a (possibly empty) sequence of atomic names. Atomic names can be either numbers or arbitrary strings. Numeric names are provided for convenience in naming lists of things, such as a row of ten squares, or the vertices of a path.
Instaces of IsName
are things which can be converted to names.
class Qualifiable a whereSource
Instances of Qualifiable
are things which can be qualified by
prefixing them with a name.
Qualifiable Name | Names can be qualified by prefixing them with other names. |
Qualifiable (NameMap v) |
|
(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 n, IsName m) => n -> m -> NameSource
Convenient operator for writing complete names in the form a1 |>
a2 |> a3 ||> a4
. In particular, n1 ||> n2
is equivalent to
n1 |> toName n2
.
A NameMap
is a map from names to points, possibly with
multiple points associated with each name.
Action Name (NameMap v) | A name acts on a name map by qualifying every name in it. |
Monoid (NameMap v) |
|
VectorSpace v => HasOrigin (NameMap v) | |
Qualifiable (NameMap v) |
|
HasLinearMap v => Transformable (NameMap v) |
fromNames :: IsName n => [(n, Point v)] -> NameMap vSource
Construct a NameMap
from a list of (name, point) pairs.
lookupN :: IsName n => n -> NameMap v -> Maybe [Point v]Source
Look for the given name in a name map, returning a list of points 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
An existential wrapper type to hold attributes. Some attributes are affected by transformations and some are not.
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.
A Style
is a heterogeneous collection of attributes, containing
at most one attribute of any given type.
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. |
Type class for things which have a style.
applyStyle :: Style (V a) -> a -> aSource
Apply a style by combining it (on the left) with the existing style.
HasStyle a => HasStyle [a] | |
HasStyle (Style v) | |
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v), Monoid m) => HasStyle (AnnDiagram b v m) |
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
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 ofu
ontov
iss' *^ v
, thens' <= 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.
(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 |
(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.
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.
Boundable b => Boundable [b] | |
(InnerSpace v, OrderedField (Scalar v)) => Boundable (Bounds v) | |
(HasLinearMap v, InnerSpace v, OrderedField (Scalar v)) => Boundable (AnnDiagram b v m) |
boundary :: Boundable a => V a -> a -> Point (V a)Source
Compute the point along the boundary in the given direction.
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, Trail
s) are
transformable but are translationally invariant, i.e. have no
origin.
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.
HasOrigin a => HasOrigin [a] | |
VectorSpace v => HasOrigin (Point v) | |
VectorSpace v => HasOrigin (NameMap 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. |
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
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.
Functor (Query v) | |
Applicative (Query v) | |
Monoid m => Monoid (Query v m) | |
VectorSpace v => HasOrigin (Query v m) | |
HasLinearMap v => Transformable (Query v m) |
Primtives
A value of type Prim b v
is an opaque (existentially quantified)
primitive which backend b
knows how to render in vector space v
.
Prim :: Renderable t b => t -> Prim b (V t) |
HasLinearMap v => Transformable (Prim b v) | The |
HasLinearMap v => Renderable (Prim b v) b | The |
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.
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, 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, 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) => 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 :: 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.
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 a 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) -> n -> AnnDiagram b v m -> AnnDiagram b v mSource
Attach a name to the given point in this diagram.
withName :: HasLinearMap v => Name -> (Point 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, perform the transformation using the first point associated with the name, or perform the identity transformation if the name does 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 :: (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
.
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 = (>>)
.
The result of running/interpreting a rendering operation.
Backend-specific rendering options.
:: 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.
:: 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.
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.
HasLinearMap v => Backend () v | The trivial backend which does nothing. Useful for fixing the type of diagrams whose rendering behavior we really don't care about (e.g. diagrams we are just going to use for bounding other diagrams, etc.) |
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.
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.
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.
(HasLinearMap v, Monoid (Render b v)) => Renderable (NullPrim v) b | |
HasLinearMap v => Renderable (Prim b v) b | The |
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.
(HasBasis v, HasTrie (Basis v), VectorSpace v) => HasLinearMap v |
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.
(Fractional s, Floating s, Ord s, AdditiveGroup s) => OrderedField s |