diagrams-core-1.3: Core libraries for diagrams EDSL

Copyright(c) 2011-2015 diagrams-core team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Core.Names

Contents

Description

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

Synopsis

Names

Atomic names

data AName where Source

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

Constructors

AName :: (Typeable a, Ord a, Show a) => a -> AName 

_AName :: (Typeable a, Ord a, Show a) => Prism' AName a Source

Prism onto 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 
Semigroup Name 
Wrapped Name 
Qualifiable Name

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

IsName Name 
Typeable * Name 
Rewrapped Name Name 
Action Name a => Action Name (Deletable a) 
Action Name (Trace v n) 
Action Name (Envelope v n) 
Action Name (Query v n m) 
Action Name (SubMap b v n m)

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

type Unwrapped Name = [AName] 

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

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.

To make an instance of IsName, you need not define any methods, just declare it.

WARNING: it is not recommended to use GeneralizedNewtypeDeriving in conjunction with IsName, since in that case the underlying type and the newtype will be considered equivalent when comparing names. For example:

    newtype WordN = WordN Int deriving (Show, Ord, Eq, Typeable, IsName)
  

is unlikely to work as intended, since (1 :: Int) and (WordN 1) will be considered equal as names. Instead, use

    newtype WordN = WordN Int deriving (Show, Ord, Eq, Typeable, IsName)
    instance IsName WordN
  

Minimal complete definition

Nothing

Methods

toName :: a -> Name Source

Instances

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

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.

Qualifiable

class Qualifiable q where Source

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

Methods

(.>>) :: IsName a => a -> q -> q infixr 5 Source

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 (b -> a) 
(Qualifiable a, Qualifiable b) => Qualifiable (a, b) 
Qualifiable a => Qualifiable (Map k a) 
Qualifiable a => Qualifiable (Measured n a) 
(Qualifiable a, Qualifiable b, Qualifiable c) => Qualifiable (a, b, c) 
Qualifiable (SubMap b v n m)

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

(Metric v, OrderedField n, Semigroup m) => Qualifiable (QDiagram b v n m)

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