| Copyright | (c) 2011-2015 diagrams-core team (see LICENSE) | 
|---|---|
| License | BSD-style (see LICENSE) | 
| Maintainer | diagrams-discuss@googlegroups.com | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Diagrams.Core.Names
Description
This module defines a type of names which can be used for referring to subdiagrams, and related types.
Names
Atomic names
Names
A (qualified) name is a (possibly empty) sequence of atomic names.
Instances
| Monoid Name Source # | |
| Semigroup Name Source # | |
| Show Name Source # | |
| IsName Name Source # | |
| Qualifiable Name Source # | Of course, names can be qualified using  | 
| Eq Name Source # | |
| Ord Name Source # | |
| Wrapped Name Source # | |
| Rewrapped Name Name Source # | |
| Defined in Diagrams.Core.Names | |
| Each Name Name AName AName Source # | |
| Action Name a => Action Name (Deletable a) Source # | |
| Action Name (Envelope v n) Source # | |
| Action Name (Trace v n) Source # | |
| Action Name (Query v n m) Source # | |
| Action Name (SubMap b v n m) Source # | A name acts on a name map by qualifying every name in it. | 
| type Unwrapped Name Source # | |
| Defined in Diagrams.Core.Names | |
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
Instances
| IsName AName Source # | |
| IsName Name Source # | |
| IsName Integer Source # | |
| IsName () Source # | |
| Defined in Diagrams.Core.Names | |
| IsName Bool Source # | |
| IsName Char Source # | |
| IsName Double Source # | |
| IsName Float Source # | |
| IsName Int Source # | |
| IsName a => IsName (Maybe a) Source # | |
| IsName a => IsName [a] Source # | |
| Defined in Diagrams.Core.Names | |
| (IsName a, IsName b) => IsName (a, b) Source # | |
| Defined in Diagrams.Core.Names | |
| (IsName a, IsName b, IsName c) => IsName (a, b, c) Source # | |
| Defined in Diagrams.Core.Names | |
(.>) :: (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.
eachName :: (Typeable a, Ord a, Show a) => Traversal' Name a Source #
Traversal over each name in a Name that matches the target type.
>>> toListOf eachName (a.> False .>b) :: String "ab" >>>a.> True .>b& eachName %~ nota.> False .>b
Note that the type of the name is very important.
>>> sumOf eachName ((1::Int) .> (2 :: Integer) .> (3 :: Int)) :: Int 4 >>> sumOf eachName ((1::Int) .> (2 :: Integer) .> (3 :: Int)) :: Integer 2
Qualifiable
class Qualifiable q where Source #
Instances of Qualifiable are things which can be qualified by
   prefixing them with a name.
Instances
| Qualifiable Name Source # | Of course, names can be qualified using  | 
| (Ord a, Qualifiable a) => Qualifiable (Set a) Source # | |
| Qualifiable a => Qualifiable (TransInv a) Source # | |
| Qualifiable a => Qualifiable [a] Source # | |
| Defined in Diagrams.Core.Names | |
| Qualifiable a => Qualifiable (Map k a) Source # | |
| Qualifiable a => Qualifiable (Measured n a) Source # | |
| Qualifiable a => Qualifiable (b -> a) Source # | |
| Defined in Diagrams.Core.Names | |
| (Qualifiable a, Qualifiable b) => Qualifiable (a, b) Source # | |
| Defined in Diagrams.Core.Names | |
| (Qualifiable a, Qualifiable b, Qualifiable c) => Qualifiable (a, b, c) Source # | |
| Defined in Diagrams.Core.Names | |
| (Metric v, OrderedField n, Semigroup m) => Qualifiable (QDiagram b v n m) Source # | Diagrams can be qualified so that all their named points can now be referred to using the qualification prefix. | 
| Qualifiable (SubMap b v n m) Source # | 
 |