{-# LANGUAGE DeriveGeneric #-}
module Cryptol.Parser.Name where
import Cryptol.Utils.Ident
import Cryptol.Utils.PP
import Cryptol.Utils.Panic (panic)
import Control.DeepSeq
import GHC.Generics (Generic)
data PName = UnQual !Ident
| Qual !ModName !Ident
| NewName !Pass !Int
deriving (Eq,Ord,Show,Generic)
data Pass = NoPat
| MonoValues
deriving (Eq,Ord,Show,Generic)
instance NFData PName
instance NFData Pass
mkUnqual :: Ident -> PName
mkUnqual = UnQual
mkQual :: ModName -> Ident -> PName
mkQual = Qual
getModName :: PName -> Maybe ModName
getModName (Qual ns _) = Just ns
getModName _ = Nothing
getIdent :: PName -> Ident
getIdent (UnQual n) = n
getIdent (Qual _ n) = n
getIdent (NewName p i) = packIdent ("__" ++ pass ++ show i)
where
pass = case p of
NoPat -> "p"
MonoValues -> "mv"
isGeneratedName :: PName -> Bool
isGeneratedName x =
case x of
NewName {} -> True
_ -> False
instance PP PName where
ppPrec _ = ppPrefixName
instance PPName PName where
ppNameFixity n
| isInfixIdent i = Just (NonAssoc, 0)
| otherwise = Nothing
where
i = getIdent n
ppPrefixName n = optParens (isInfixIdent i) (pfx <.> pp i)
where
i = getIdent n
pfx = case getModName n of
Just ns -> pp ns <.> text "::"
Nothing -> empty
ppInfixName n
| isInfixIdent i = pfx <.> pp i
| otherwise = panic "AST" [ "non-symbol infix name:" ++ show n ]
where
i = getIdent n
pfx = case getModName n of
Just ns -> pp ns <.> text "::"
Nothing -> empty