module Ideas.Common.Id
(
Id, IsId(..), ( # )
, HasId(..), unqualified, qualifiers, qualification
, describe, description, showId, compareId
, Identify(..)
, module Data.Monoid
, (<>)
) where
import Control.Monad
import Data.Char
import Data.List
import Data.Monoid hiding ((<>))
import Data.Ord
import Data.Semigroup as Sem
import Ideas.Common.Classes
import Ideas.Utils.Prelude (splitsWithElem)
import Ideas.Utils.StringRef
import Test.QuickCheck
data Id = Id
{ idList :: [String]
, idDescription :: String
, idRef :: !StringRef
}
instance Show Id where
show = intercalate "." . idList
instance Read Id where
readsPrec _ =
return . mapFirst stringId . span isIdChar . dropWhile isSpace
instance Eq Id where
a == b = idRef a == idRef b
instance Ord Id where
compare = comparing idRef
instance Sem.Semigroup Id where
(<>) = ( # )
instance Monoid Id where
mempty = emptyId
mappend = (<>)
instance Arbitrary Id where
arbitrary = frequency
[ (4, do n <- choose (0, 8)
xs <- replicateM n (elements ['a' .. 'z'])
return $ newId xs)
, (1, liftM2 mappend arbitrary arbitrary)
]
class IsId a where
newId :: a -> Id
concatId :: [a] -> Id
concatId = mconcat . map newId
instance IsId Id where
newId = id
instance IsId Char where
newId c = stringId [c]
concatId = stringId
instance IsId a => IsId [a] where
newId = concatId
concatId = mconcat . map newId
instance IsId () where
newId = const emptyId
instance (IsId a, IsId b) => IsId (a, b) where
newId (a, b) = newId a # newId b
instance (IsId a, IsId b, IsId c) => IsId (a, b, c) where
newId (a, b, c) = newId a # newId b # newId c
instance IsId a => IsId (Maybe a) where
newId = maybe emptyId newId
instance (IsId a, IsId b) => IsId (Either a b) where
newId = either newId newId
infixr 8 #
( # ) :: (IsId a, IsId b) => a -> b -> Id
a # b = appendId (newId a) (newId b)
class HasId a => Identify a where
(@>) :: IsId n => n -> a -> a
class HasId a where
getId :: a -> Id
changeId :: (Id -> Id) -> a -> a
instance HasId Id where
getId = id
changeId = id
instance (HasId a, HasId b) => HasId (Either a b) where
getId = either getId getId
changeId f = biMap (changeId f) (changeId f)
appendId :: Id -> Id -> Id
appendId a b
| null (idList a) = b
| null (idList b) = a
| otherwise = Id (idList a ++ idList b) "" ref
where
ref = stringRef (show a ++ "." ++ show b)
stringId :: String -> Id
stringId txt = Id (make s) "" (stringRef s)
where
s = norm txt
make = filter (not . null) . splitsWithElem '.'
norm = filter isIdChar . map toLower
isIdChar :: Char -> Bool
isIdChar c = isAlphaNum c || c `elem` ".-_"
emptyId :: Id
emptyId = Id [] "" (stringRef "")
unqualified :: HasId a => a -> String
unqualified a
| null xs = ""
| otherwise = last xs
where
xs = idList (getId a)
qualifiers :: HasId a => a -> [String]
qualifiers a
| null xs = []
| otherwise = init xs
where
xs = idList (getId a)
qualification :: HasId a => a -> String
qualification = intercalate "." . qualifiers
description :: HasId a => a -> String
description = idDescription . getId
describe :: HasId a => String -> a -> a
describe = changeId . describeId
where
describeId s a
| null (idDescription a) =
a {idDescription = s}
| otherwise =
a {idDescription = s ++ " " ++ idDescription a}
showId :: HasId a => a -> String
showId = show . getId
compareId :: HasId a => a -> a -> Ordering
compareId = comparing showId