module PGF.CId (CId(..),
mkCId, wildCId,
readCId, showCId,
pCId, pIdent, ppCId) where
import Control.Monad
import qualified Data.ByteString.Char8 as BS
import Data.Char
import qualified Text.ParserCombinators.ReadP as RP
import qualified Text.PrettyPrint as PP
newtype CId = CId BS.ByteString deriving (Eq,Ord)
wildCId :: CId
wildCId = CId (BS.singleton '_')
mkCId :: String -> CId
mkCId s = CId (BS.pack s)
readCId :: String -> Maybe CId
readCId s = case [x | (x,cs) <- RP.readP_to_S pCId s, all isSpace cs] of
[x] -> Just x
_ -> Nothing
showCId :: CId -> String
showCId (CId x) = BS.unpack x
instance Show CId where
showsPrec _ = showString . showCId
instance Read CId where
readsPrec _ = RP.readP_to_S pCId
pCId :: RP.ReadP CId
pCId = do s <- pIdent
if s == "_"
then RP.pfail
else return (mkCId s)
pIdent :: RP.ReadP String
pIdent = liftM2 (:) (RP.satisfy isIdentFirst) (RP.munch isIdentRest)
where
isIdentFirst c = c == '_' || isLetter c
isIdentRest c = c == '_' || c == '\'' || isAlphaNum c
ppCId :: CId -> PP.Doc
ppCId = PP.text . showCId