diagrams-lib-1.0: Embedded domain-specific language for declarative graphics

Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone

Diagrams.Names

Contents

Description

Names can be given to subdiagrams, and subdiagrams can later be queried by name. This module exports types for representing names and subdiagrams, and various functions for working with them.

Synopsis

Names

data AName

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

data Name

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

Instances

Eq Name 
Ord Name 
Show Name 
Typeable Name 
Semigroup Name 
Monoid Name 
IsName Name 
Qualifiable Name

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

Action Name (Envelope v) 
Action Name (Trace v) 
Action Name a => Action Name (Deletable a) 
Action Name (Query v m) 
Action Name (SubMap b v m)

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

Wrapped [AName] [AName] Name Name 
Wrapped (Map Name [Subdiagram b v m]) (Map Name [Subdiagram b v m']) (SubMap b v m) (SubMap 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') 

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

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 -> Name

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

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.

class Qualifiable q where

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

Methods

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

Qualify with the given name.

Instances

Qualifiable Name

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

Qualifiable a => Qualifiable [a] 
(Ord a, Qualifiable a) => Qualifiable (Set a) 
Qualifiable a => Qualifiable (TransInv a) 
Qualifiable a => Qualifiable (Located a) 
Qualifiable a => Qualifiable (b -> a) 
(Qualifiable a, Qualifiable b) => Qualifiable (a, b) 
Qualifiable a => Qualifiable (Map k a) 
(Qualifiable a, Qualifiable b, Qualifiable c) => Qualifiable (a, b, c) 
(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.

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.

Subdiagrams

data Subdiagram b v m

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

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

Turn a diagram into a subdiagram with no accumulated context.

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

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.

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

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 m

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

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

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

Subdiagram maps

data SubMap b v m

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

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') 
Semigroup (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.

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.

(InnerSpace v, Floating (Scalar v), HasLinearMap v) => Transformable (SubMap b v m) 
(OrderedField (Scalar v), InnerSpace v, HasLinearMap v) => HasOrigin (SubMap 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') 

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

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 m

Add a name/diagram association to a submap.

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

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.

Naming things

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

Attach an atomic name to a diagram.

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 m

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

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

Attach an atomic name to a certain point (which may be computed from the given diagram), treated as a subdiagram with no content and a point envelope.

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

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

Querying by name

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

Get a list of names of subdiagrams and their locations.

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

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 m

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 m

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 m

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.