module Diagrams.Core.Names
(
AName(..)
, _AName
, Name(..)
, IsName(..)
, (.>)
, eachName
, Qualifiable(..)
) where
import Control.Lens hiding ((.>))
import qualified Data.Map as M
import Data.Semigroup
import qualified Data.Set as S
import Data.Typeable
import Diagrams.Core.Transform
import Diagrams.Core.Measure
class (Typeable a, Ord a, Show a) => IsName a where
toName :: a -> Name
toName = Name . (:[]) . AName
instance IsName ()
instance IsName Bool
instance IsName Char
instance IsName Int
instance IsName Float
instance IsName Double
instance IsName Integer
instance IsName a => IsName [a]
instance IsName a => IsName (Maybe a)
instance (IsName a, IsName b) => IsName (a,b)
instance (IsName a, IsName b, IsName c) => IsName (a,b,c)
data AName where
AName :: (Typeable a, Ord a, Show a) => a -> AName
deriving Typeable
instance IsName AName where
toName = Name . (:[])
instance Eq AName where
AName a1 == AName a2 =
case cast a2 of
Nothing -> False
Just a2' -> a1 == a2'
instance Ord AName where
AName a1 `compare` AName a2 =
case cast a2 of
Just a2' -> a1 `compare` a2'
Nothing -> typeOf a1 `compare` typeOf a2
instance Show AName where
showsPrec d (AName a) = showParen (d > 10) $
showString "AName " . showsPrec 11 a
_AName :: (Typeable a, Ord a, Show a) => Prism' AName a
_AName = prism' AName (\(AName a) -> cast a)
newtype Name = Name [AName]
deriving (Eq, Ord, Semigroup, Monoid, Typeable)
instance Rewrapped Name Name
instance Wrapped Name where
type Unwrapped Name = [AName]
_Wrapped' = iso (\(Name ns) -> ns) Name
instance Each Name Name AName AName where
each = _Wrapped . traversed
eachName :: (Typeable a, Ord a, Show a) => Traversal' Name a
eachName = each . _AName
instance Show Name where
showsPrec d (Name xs) = case xs of
[] -> showParen (d > 10) $ showString "toName []"
[n] -> showParen (d > 10) $ showString "toName " . showsName 11 n
(n:ns) -> showParen (d > 5) $ showsName 6 n . go ns
where
go (y:ys) = showString " .> " . showsName 6 y . go ys
go _ = id
where showsName dd (AName a) = showsPrec dd a
instance IsName Name where
toName = id
(.>) :: (IsName a1, IsName a2) => a1 -> a2 -> Name
a1 .> a2 = toName a1 <> toName a2
class Qualifiable q where
(.>>) :: IsName a => a -> q -> q
instance Qualifiable Name where
(.>>) = (.>)
instance Qualifiable a => Qualifiable (TransInv a) where
(.>>) n = over (_Unwrapping' TransInv) (n .>>)
instance (Qualifiable a, Qualifiable b) => Qualifiable (a,b) where
n .>> (a,b) = (n .>> a, n .>> b)
instance (Qualifiable a, Qualifiable b, Qualifiable c) => Qualifiable (a,b,c) where
n .>> (a,b,c) = (n .>> a, n .>> b, n .>> c)
instance Qualifiable a => Qualifiable [a] where
n .>> as = map (n .>>) as
instance (Ord a, Qualifiable a) => Qualifiable (S.Set a) where
n .>> s = S.map (n .>>) s
instance Qualifiable a => Qualifiable (M.Map k a) where
n .>> m = fmap (n .>>) m
instance Qualifiable a => Qualifiable (b -> a) where
n .>> f = (n .>>) . f
instance Qualifiable a => Qualifiable (Measured n a) where
n .>> m = fmap (n .>>) m
infixr 5 .>>
infixr 5 .>