module Casui.Name where import Casui.Utils import Data.Unique import Data.List type Symbol = String class HasName t where nameOf :: t -> Name instance HasName Name where nameOf = id instance HasName FullName where nameOf (FullName Builtin l) = Name $ "builtin" : l nameOf (FullName _ l) = Name $ l matchName :: Name -> FullName -> Bool matchName (Name n) (FullName i fn) = case dropSame (reverse n) (reverse fn) of ([], _) -> True (["builtin"],[]) -> i == Builtin _otherwise -> False data Name = Name [Symbol] deriving Eq data FullName = FullName FileId [Symbol] deriving Eq data FileId = Builtin | Lexical | FileId Unique deriving Eq instance Show Name where show (Name l) = (concat $ intersperse ":" l) instance Show FullName where show (FullName i l) = concat $ intersperse ":" $ if show i == "" then l else show i : l instance Show FileId where show Builtin = "builtin" show Lexical = "lexical" show (FileId i) = "#e" ++ show (hashUnique i) instance FName Name where fullName e s = Name $ show e : splitChar ':' s instance FName FullName where fullName i s = FullName i $ splitChar ':' s builtin :: FName n => String -> n builtin s = fullName Builtin s class (Eq n, Show n) => FName n where fullName :: FileId -> String -> n mkName :: String -> Name mkName = Name . splitChar ':' catNames :: Name -> Name -> Name catNames (Name a) (Name b) = Name $ a ++ b