diagrams-core-0.3: Core libraries for diagrams EDSL

Maintainerdiagrams-discuss@googlegroups.com

Graphics.Rendering.Diagrams.Names

Contents

Description

This module defines a type of names which can be used for referring to locations within diagrams, and related types.

Synopsis

Names

Atomic names

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

Atomic types are those 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

toAName :: a -> ANameSource

Instances

data AName whereSource

Atomic names. AName is just an existential wrapper around Atomic values.

Constructors

AName :: Atomic a => a -> AName 

Names

newtype Name Source

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

Constructors

Name [AName] 

Instances

Eq Name 
Ord Name 
Show Name 
Monoid Name 
Qualifiable Name

Of course, names can be qualified.

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.

toName :: Atomic a => a -> NameSource

Convert an atomic name to a name.

Qualifiable

class Qualifiable q whereSource

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

Methods

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

Qualify with the given name.

Instances

Qualifiable Name

Of course, names can be qualified.

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.

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

Convenient operator for writing complete names in the form a1 |> a2 |> a3 ||> a4. In particular, a1 .> a2 is equivalent to a1 |> toName a2.

(||>) :: Qualifiable q => Name -> q -> qSource

Qualify by an entire qualified name. (a1 |> a2 .> a3) ||> q is equivalent to a1 |> a2 |> a3 |> q.

Name maps

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

Constructors

NameMap (Map Name [(Point v, TransInv (Bounds v))]) 

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.

Constructing name maps

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

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

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

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

rememberAs :: Name -> Point v -> Bounds v -> NameMap v -> NameMap vSource

Give a name to a point and bounding function.

Searching within name maps

lookupN :: Name -> 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.