module Lexeme (
isLexCon, isLexVar, isLexId, isLexSym,
isLexConId, isLexConSym, isLexVarId, isLexVarSym,
startsVarSym, startsVarId, startsConSym, startsConId,
okVarOcc, okConOcc, okTcOcc,
okVarIdOcc, okVarSymOcc, okConIdOcc, okConSymOcc
) where
import GhcPrelude
import FastString
import Data.Char
import qualified Data.Set as Set
import GHC.Lexeme
isLexCon, isLexVar, isLexId, isLexSym :: FastString -> Bool
isLexConId, isLexConSym, isLexVarId, isLexVarSym :: FastString -> Bool
isLexCon cs = isLexConId cs || isLexConSym cs
isLexVar cs = isLexVarId cs || isLexVarSym cs
isLexId cs = isLexConId cs || isLexVarId cs
isLexSym cs = isLexConSym cs || isLexVarSym cs
isLexConId cs
| nullFS cs = False
| cs == (fsLit "[]") = True
| otherwise = startsConId (headFS cs)
isLexVarId cs
| nullFS cs = False
| otherwise = startsVarId (headFS cs)
isLexConSym cs
| nullFS cs = False
| cs == (fsLit "->") = True
| otherwise = startsConSym (headFS cs)
isLexVarSym fs
| fs == (fsLit "~R#") = True
| otherwise
= case (if nullFS fs then [] else unpackFS fs) of
[] -> False
(c:cs) -> startsVarSym c && all isVarSymChar cs
okVarOcc :: String -> Bool
okVarOcc str@(c:_)
| startsVarId c
= okVarIdOcc str
| startsVarSym c
= okVarSymOcc str
okVarOcc _ = False
okConOcc :: String -> Bool
okConOcc str@(c:_)
| startsConId c
= okConIdOcc str
| startsConSym c
= okConSymOcc str
| str == "[]"
= True
okConOcc _ = False
okTcOcc :: String -> Bool
okTcOcc "[]" = True
okTcOcc "->" = True
okTcOcc "~" = True
okTcOcc str@(c:_)
| startsConId c
= okConIdOcc str
| startsConSym c
= okConSymOcc str
| startsVarSym c
= okVarSymOcc str
okTcOcc _ = False
okVarIdOcc :: String -> Bool
okVarIdOcc str = okIdOcc str &&
(str == "_" || not (str `Set.member` reservedIds))
okVarSymOcc :: String -> Bool
okVarSymOcc str = all okSymChar str &&
not (str `Set.member` reservedOps) &&
not (isDashes str)
okConIdOcc :: String -> Bool
okConIdOcc str = okIdOcc str ||
is_tuple_name1 True str ||
is_tuple_name1 False str ||
is_sum_name1 str
where
is_tuple_name1 True ('(' : rest) = is_tuple_name2 True rest
is_tuple_name1 False ('(' : '#' : rest) = is_tuple_name2 False rest
is_tuple_name1 _ _ = False
is_tuple_name2 True ")" = True
is_tuple_name2 False "#)" = True
is_tuple_name2 boxed (',' : rest) = is_tuple_name2 boxed rest
is_tuple_name2 boxed (ws : rest)
| isSpace ws = is_tuple_name2 boxed rest
is_tuple_name2 _ _ = False
is_sum_name1 ('(' : '#' : rest) = is_sum_name2 False rest
is_sum_name1 _ = False
is_sum_name2 _ "#)" = True
is_sum_name2 underscore ('|' : rest) = is_sum_name2 underscore rest
is_sum_name2 False ('_' : rest) = is_sum_name2 True rest
is_sum_name2 underscore (ws : rest)
| isSpace ws = is_sum_name2 underscore rest
is_sum_name2 _ _ = False
okConSymOcc :: String -> Bool
okConSymOcc ":" = True
okConSymOcc str = all okSymChar str &&
not (str `Set.member` reservedOps)
okIdOcc :: String -> Bool
okIdOcc str
= let hashes = dropWhile okIdChar str in
all (== '#') hashes
okIdChar :: Char -> Bool
okIdChar c = case generalCategory c of
UppercaseLetter -> True
LowercaseLetter -> True
TitlecaseLetter -> True
ModifierLetter -> True
OtherLetter -> True
NonSpacingMark -> True
DecimalNumber -> True
OtherNumber -> True
_ -> c == '\'' || c == '_'
reservedIds :: Set.Set String
reservedIds = Set.fromList [ "case", "class", "data", "default", "deriving"
, "do", "else", "foreign", "if", "import", "in"
, "infix", "infixl", "infixr", "instance", "let"
, "module", "newtype", "of", "then", "type", "where"
, "_" ]
reservedOps :: Set.Set String
reservedOps = Set.fromList [ "..", ":", "::", "=", "\\", "|", "<-", "->"
, "@", "~", "=>" ]
isDashes :: String -> Bool
isDashes ('-' : '-' : rest) = all (== '-') rest
isDashes _ = False