module Compiler.Lexer.Identifiers where import Common import Control.Applicative import Data.Char import Data.String import Data.Text as T import Parser import Test.Common newtype Identifier = Identifier { unIdentifer :: Text } deriving (Show, Eq, Ord) instance IsString Identifier where fromString = Identifier . T.pack instance HasParser Identifier where parser = (\x -> Identifier $ pack x) <$> (do s <- pAny isAsciiLower rst <- many (pAny (\x -> isAlphaNum x || x == '_')) pure (s : rst) ) instance ToSource Identifier where toSource = unIdentifer instance HasGen Identifier where getGen = Identifier <$> choice [ gen , do x <- gen; s <- int (linear 0 999); pure (x <> (pack $ show s)) ] where gen = ((pack . (\x -> "identi" <> x)) <$> (list (linear 1 10) (choice [lower, upper])))