megaparsec/Text/Megaparsec/Token.hs

584 lines
19 KiB
Haskell
Raw Normal View History

2008-01-13 20:53:15 +03:00
-- |
-- Module : Text.Megaparsec.Token
-- Copyright : © 2015 Megaparsec contributors
-- © 2007 Paolo Martini
-- © 19992001 Daan Leijen
2015-07-28 16:32:19 +03:00
-- License : BSD3
--
-- Maintainer : Mark Karpov <markkarpov@opmbx.org>
2015-07-29 11:38:32 +03:00
-- Stability : experimental
2008-01-20 09:39:18 +03:00
-- Portability : non-portable (uses local universal quantification: PolymorphicComponents)
2015-07-28 16:32:19 +03:00
--
-- A helper module to parse lexical elements (tokens). See 'makeTokenParser'
-- for a description of how to use it.
2008-01-13 20:53:15 +03:00
2008-02-13 07:32:24 +03:00
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
2008-01-13 20:53:15 +03:00
module Text.Megaparsec.Token
2015-08-12 20:51:06 +03:00
( LanguageDef (..)
, TokenParser (..)
, makeTokenParser )
2015-07-28 16:32:19 +03:00
where
2008-01-13 20:53:15 +03:00
import Control.Applicative ((<|>), many, some)
import Control.Monad (void)
import Data.Char (isAlpha, toLower, toUpper)
import Data.List (sort)
2015-07-30 18:45:06 +03:00
import Text.Megaparsec.Prim
import Text.Megaparsec.Char
import Text.Megaparsec.Combinator
2008-01-13 20:53:15 +03:00
2015-07-30 18:45:06 +03:00
-- Language definition
2015-08-12 15:41:22 +03:00
-- | The @LanguageDef@ type is a record that contains all parameters used to
-- control features of the "Text.Megaparsec.Token" module. The module
-- "Text.Megaparsec.Language" contains some default definitions.
2015-07-30 21:36:54 +03:00
data LanguageDef s u m =
2015-08-12 20:51:06 +03:00
LanguageDef {
2015-07-28 16:32:19 +03:00
2015-08-12 20:51:06 +03:00
-- | Describes the start of a block comment. Use the empty string if the
-- language doesn't support block comments.
2015-08-12 20:51:06 +03:00
commentStart :: String
2015-08-12 20:51:06 +03:00
-- | Describes the end of a block comment. Use the empty string if the
-- language doesn't support block comments.
2015-08-12 20:51:06 +03:00
, commentEnd :: String
2015-08-12 20:51:06 +03:00
-- | Describes the start of a line comment. Use the empty string if the
-- language doesn't support line comments.
2015-08-12 20:51:06 +03:00
, commentLine :: String
2015-08-12 20:51:06 +03:00
-- | Set to 'True' if the language supports nested block comments.
2015-08-12 20:51:06 +03:00
, nestedComments :: Bool
2015-08-12 20:51:06 +03:00
-- | This parser should accept any start characters of identifiers, for
-- example @letter \<|> char \'_\'@.
2015-08-12 20:51:06 +03:00
, identStart :: ParsecT s u m Char
2015-08-12 20:51:06 +03:00
-- | This parser should accept any legal tail characters of identifiers,
-- for example @alphaNum \<|> char \'_\'@.
2015-08-12 20:51:06 +03:00
, identLetter :: ParsecT s u m Char
2015-08-12 20:51:06 +03:00
-- | This parser should accept any start characters of operators, for
-- example @oneOf \":!#$%&*+.\/\<=>?\@\\\\^|-~\"@
2015-08-12 20:51:06 +03:00
, opStart :: ParsecT s u m Char
2015-08-12 20:51:06 +03:00
-- | This parser should accept any legal tail characters of operators.
-- Note that this parser should even be defined if the language doesn't
-- support user-defined operators, or otherwise the 'reservedOp' parser
-- won't work correctly.
2015-08-12 20:51:06 +03:00
, opLetter :: ParsecT s u m Char
2015-08-12 20:51:06 +03:00
-- | The list of reserved identifiers.
2015-08-12 20:51:06 +03:00
, reservedNames :: [String]
2015-08-12 20:51:06 +03:00
-- | The list of reserved operators.
2015-08-12 20:51:06 +03:00
, reservedOpNames :: [String]
2015-08-12 20:51:06 +03:00
-- | Set to 'True' if the language is case sensitive.
2015-08-12 20:51:06 +03:00
, caseSensitive :: Bool }
2008-01-13 20:53:15 +03:00
2015-07-30 21:36:54 +03:00
-- Token parser
-- | The type of the record that holds lexical parsers that work on
-- @s@ streams with state @u@ over a monad @m@.
2015-07-30 21:36:54 +03:00
data TokenParser s u m =
2015-08-12 20:51:06 +03:00
TokenParser {
2015-08-12 20:51:06 +03:00
-- | The lexeme parser parses a legal identifier. Returns the identifier
-- string. This parser will fail on identifiers that are reserved
-- words. Legal identifier (start) characters and reserved words are
-- defined in the 'LanguageDef' that is passed to 'makeTokenParser'.
2015-07-28 16:32:19 +03:00
2015-08-12 20:51:06 +03:00
identifier :: ParsecT s u m String
2015-08-12 20:51:06 +03:00
-- | The lexeme parser @reserved name@ parses @symbol name@, but it also
-- checks that the @name@ is not a prefix of a valid identifier.
2015-08-12 20:51:06 +03:00
, reserved :: String -> ParsecT s u m ()
2015-08-12 20:51:06 +03:00
-- | The lexeme parser parses a legal operator. Returns the name of the
-- operator. This parser will fail on any operators that are reserved
-- operators. Legal operator (start) characters and reserved operators are
-- defined in the 'LanguageDef' that is passed to 'makeTokenParser'.
2015-08-12 20:51:06 +03:00
, operator :: ParsecT s u m String
2015-08-12 20:51:06 +03:00
-- | The lexeme parser @reservedOp name@ parses @symbol name@, but it
-- also checks that the @name@ is not a prefix of a valid operator.
2015-08-12 20:51:06 +03:00
, reservedOp :: String -> ParsecT s u m ()
2015-08-12 20:51:06 +03:00
-- | The lexeme parser parses a single literal character. Returns the
-- literal character value. This parsers deals correctly with escape
-- sequences. The literal character is parsed according to the grammar
-- rules defined in the Haskell report (which matches most programming
-- languages quite closely).
2015-08-12 20:51:06 +03:00
, charLiteral :: ParsecT s u m Char
2015-08-12 20:51:06 +03:00
-- | The lexeme parser parses a literal string. Returns the literal
-- string value. This parsers deals correctly with escape sequences and
-- gaps. The literal string is parsed according to the grammar rules
-- defined in the Haskell report (which matches most programming languages
-- quite closely).
2015-08-12 20:51:06 +03:00
, stringLiteral :: ParsecT s u m String
2015-08-12 20:51:06 +03:00
-- | The lexeme parser parses an integer (a whole number). This parser
-- /does not/ parse sign. Returns the value of the number. The number can
-- be specified in 'decimal', 'hexadecimal' or 'octal'. The number is
-- parsed according to the grammar rules in the Haskell report.
2015-07-28 16:32:19 +03:00
2015-08-12 20:51:06 +03:00
, integer :: ParsecT s u m Integer
2015-08-12 20:51:06 +03:00
-- | This is just like 'integer', except it can parse sign.
2015-08-12 20:51:06 +03:00
, integer' :: ParsecT s u m Integer
2015-08-12 20:51:06 +03:00
-- | The lexeme parses a positive whole number in the decimal system.
-- Returns the value of the number.
2015-08-12 20:51:06 +03:00
, decimal :: ParsecT s u m Integer
2015-08-12 20:51:06 +03:00
-- | The lexeme parses a positive whole number in the hexadecimal
-- system. The number should be prefixed with “0x” or “0X”. Returns the
-- value of the number.
2015-08-12 20:51:06 +03:00
, hexadecimal :: ParsecT s u m Integer
2015-08-12 20:51:06 +03:00
-- | The lexeme parses a positive whole number in the octal system.
-- The number should be prefixed with “0o” or “0O”. Returns the value of
-- the number.
2015-08-12 20:51:06 +03:00
, octal :: ParsecT s u m Integer
2015-08-12 20:51:06 +03:00
-- | @signed p@ tries to parse sign (i.e. “+”, “-”, or nothing) and
-- then runs parser @p@, changing sign of its result accordingly. Note
-- that there may be white space after the sign but not before it.
2015-08-12 20:51:06 +03:00
, signed :: forall a . Num a => ParsecT s u m a -> ParsecT s u m a
2015-08-12 20:51:06 +03:00
-- | The lexeme parser parses a floating point value. Returns the value
-- of the number. The number is parsed according to the grammar rules
-- defined in the Haskell report, sign is /not/ parsed, use 'float'' to
-- achieve parsing of signed floating point values.
2015-08-12 20:51:06 +03:00
, float :: ParsecT s u m Double
2015-08-12 20:51:06 +03:00
-- | This is just like 'float', except it can parse sign.
2015-08-12 20:51:06 +03:00
, float' :: ParsecT s u m Double
2015-08-12 20:51:06 +03:00
-- | The lexeme parser parses either 'integer' or a 'float'.
-- Returns the value of the number. This parser deals with any overlap in
-- the grammar rules for integers and floats. The number is parsed
-- according to the grammar rules defined in the Haskell report.
2015-08-12 20:51:06 +03:00
, number :: ParsecT s u m (Either Integer Double)
2015-08-12 20:51:06 +03:00
-- | This is just like 'number', except it can parse sign.
2015-08-12 20:51:06 +03:00
, number' :: ParsecT s u m (Either Integer Double)
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @symbol s@ parses 'string' @s@ and skips
-- trailing white space.
2015-08-12 20:51:06 +03:00
, symbol :: String -> ParsecT s u m String
2015-08-12 20:51:06 +03:00
-- | @lexeme p@ first applies parser @p@ and than the 'whiteSpace'
-- parser, returning the value of @p@. Every lexical token (lexeme) is
-- defined using @lexeme@, this way every parse starts at a point without
-- white space. Parsers that use @lexeme@ are called /lexeme/ parsers in
-- this document.
--
-- The only point where the 'whiteSpace' parser should be called
-- explicitly is the start of the main parser in order to skip any leading
-- white space.
2015-08-12 20:51:06 +03:00
, lexeme :: forall a. ParsecT s u m a -> ParsecT s u m a
2015-08-12 20:51:06 +03:00
-- | Parses any white space. White space consists of /zero/ or more
-- occurrences of a 'space', a line comment or a block (multi line)
-- comment. Block comments may be nested. How comments are started and
-- ended is defined in the 'LanguageDef' that is passed to
-- 'makeTokenParser'.
2015-08-12 20:51:06 +03:00
, whiteSpace :: ParsecT s u m ()
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @parens p@ parses @p@ enclosed in parenthesis,
-- returning the value of @p@.
2015-08-12 20:51:06 +03:00
, parens :: forall a. ParsecT s u m a -> ParsecT s u m a
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @braces p@ parses @p@ enclosed in braces (“{” and
-- “}”), returning the value of @p@.
2015-08-12 20:51:06 +03:00
, braces :: forall a. ParsecT s u m a -> ParsecT s u m a
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @angles p@ parses @p@ enclosed in angle brackets (“\<”
-- and “>”), returning the value of @p@.
2015-08-12 20:51:06 +03:00
, angles :: forall a. ParsecT s u m a -> ParsecT s u m a
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @brackets p@ parses @p@ enclosed in brackets (“[”
-- and “]”), returning the value of @p@.
2015-08-12 20:51:06 +03:00
, brackets :: forall a. ParsecT s u m a -> ParsecT s u m a
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @semicolon@ parses the character “;” and skips any
-- trailing white space. Returns the string “;”.
2015-08-12 20:51:06 +03:00
, semicolon :: ParsecT s u m String
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @comma@ parses the character “,” and skips any
-- trailing white space. Returns the string “,”.
2015-08-12 20:51:06 +03:00
, comma :: ParsecT s u m String
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @colon@ parses the character “:” and skips any
-- trailing white space. Returns the string “:”.
2015-08-12 20:51:06 +03:00
, colon :: ParsecT s u m String
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @dot@ parses the character “.” and skips any
-- trailing white space. Returns the string “.”.
2015-08-12 20:51:06 +03:00
, dot :: ParsecT s u m String
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @semiSep p@ parses /zero/ or more occurrences of @p@
-- separated by 'semicolon'. Returns a list of values returned by @p@.
2015-08-12 20:51:06 +03:00
, semicolonSep :: forall a . ParsecT s u m a -> ParsecT s u m [a]
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @semiSep1 p@ parses /one/ or more occurrences of @p@
-- separated by 'semi'. Returns a list of values returned by @p@.
2015-08-12 20:51:06 +03:00
, semicolonSep1 :: forall a . ParsecT s u m a -> ParsecT s u m [a]
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @commaSep p@ parses /zero/ or more occurrences of
-- @p@ separated by 'comma'. Returns a list of values returned by @p@.
2015-08-12 20:51:06 +03:00
, commaSep :: forall a . ParsecT s u m a -> ParsecT s u m [a]
2015-08-12 20:51:06 +03:00
-- | Lexeme parser @commaSep1 p@ parses /one/ or more occurrences of
-- @p@ separated by 'comma'. Returns a list of values returned by @p@.
2015-08-12 20:51:06 +03:00
, commaSep1 :: forall a . ParsecT s u m a -> ParsecT s u m [a] }
2015-07-30 18:45:06 +03:00
-- Given a LanguageDef, create a token parser
2015-07-30 21:36:54 +03:00
-- | The expression @makeTokenParser language@ creates a 'TokenParser'
2015-07-30 18:45:06 +03:00
-- record that contains lexical parsers that are defined using the
-- definitions in the @language@ record.
--
2015-07-30 18:45:06 +03:00
-- The use of this function is quite stylized — one imports the appropriate
-- language definition and selects the lexical parsers that are needed from
2015-07-30 21:36:54 +03:00
-- the resulting 'TokenParser'.
--
2015-07-30 18:45:06 +03:00
-- > module Main (main) where
-- >
2015-07-30 18:45:06 +03:00
-- > import Text.Parsec
-- > import qualified Text.Parsec.Token as Token
-- > import Text.Parsec.Language (haskellDef)
-- >
2015-07-30 18:45:06 +03:00
-- > -- The parser
-- > ...
2015-07-28 16:32:19 +03:00
-- >
2015-07-30 18:45:06 +03:00
-- > expr = parens expr
-- > <|> identifier
-- > <|> ...
-- >
2015-07-30 18:45:06 +03:00
-- > -- The lexer
-- > lexer = Token.makeTokenParser haskellDef
2015-07-28 16:32:19 +03:00
-- >
2015-07-30 18:45:06 +03:00
-- > parens = Token.parens lexer
-- > braces = Token.braces lexer
-- > identifier = Token.identifier lexer
-- > reserved = Token.reserved lexer
-- > ...
2015-07-30 21:36:54 +03:00
makeTokenParser :: Stream s m Char => LanguageDef s u m -> TokenParser s u m
2015-07-30 18:45:06 +03:00
makeTokenParser languageDef =
2015-08-12 20:51:06 +03:00
TokenParser
{ identifier = identifier
, reserved = reserved
, operator = operator
, reservedOp = reservedOp
, charLiteral = charLiteral
, stringLiteral = stringLiteral
, integer = integer
, integer' = integer'
, decimal = decimal
, hexadecimal = hexadecimal
, octal = octal
, signed = signed
, float = float
, float' = float'
, number = number
, number' = number'
, symbol = symbol
, lexeme = lexeme
, whiteSpace = whiteSpace
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
, parens = parens
, braces = braces
, angles = angles
, brackets = brackets
, semicolon = semicolon
, comma = comma
, colon = colon
, dot = dot
, semicolonSep = semicolonSep
, semicolonSep1 = semicolonSep1
, commaSep = commaSep
, commaSep1 = commaSep1 }
where
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
-- bracketing
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
parens = between (symbol "(") (symbol ")")
braces = between (symbol "{") (symbol "}")
angles = between (symbol "<") (symbol ">")
brackets = between (symbol "[") (symbol "]")
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
semicolon = symbol ";"
comma = symbol ","
dot = symbol "."
colon = symbol ":"
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
commaSep = (`sepBy` comma)
semicolonSep = (`sepBy` semicolon)
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
commaSep1 = (`sepBy1` comma)
semicolonSep1 = (`sepBy1` semicolon)
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
-- chars & strings
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
charLiteral = lexeme ( between (char '\'')
(char '\'' <?> "end of character")
characterChar )
<?> "character"
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
characterChar = charLetter <|> charEscape <?> "literal character"
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
charEscape = char '\\' >> escapeCode
charLetter = satisfy (\c -> (c /= '\'') && (c /= '\\') && (c > '\026'))
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
stringLiteral =
lexeme ((foldr (maybe id (:)) "" <$>
between (char '"') (char '"' <?> "end of string")
(many stringChar)) <?> "literal string")
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
stringChar = (Just <$> stringLetter) <|> stringEscape <?> "string character"
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
stringLetter = satisfy (\c -> (c /= '"') && (c /= '\\') && (c > '\026'))
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
stringEscape = char '\\' >>
( (escapeGap >> return Nothing) <|>
(escapeEmpty >> return Nothing) <|>
(Just <$> escapeCode) )
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
escapeEmpty = char '&'
escapeGap = some spaceChar >> char '\\' <?> "end of string gap"
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
-- escape codes
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
escapeCode = charEsc <|> charNum <|> charAscii <|> charControl
<?> "escape code"
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
charEsc = choice (parseEsc <$> escMap)
where parseEsc (c, code) = char c >> return code
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
charNum = toEnum . fromInteger <$>
( decimal <|>
(char 'o' >> nump "0o" octDigitChar) <|>
(char 'x' >> nump "0x" hexDigitChar) )
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
charAscii = choice (parseAscii <$> asciiMap)
where parseAscii (asc, code) = try (string asc >> return code)
2015-08-12 20:51:06 +03:00
charControl = toEnum . subtract 64 . fromEnum <$> (char '^' >> upperChar)
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
-- escape code tables
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
escMap = zip "abfnrtv\\\"\'" "\a\b\f\n\r\t\v\\\"\'"
asciiMap = zip (ascii3codes ++ ascii2codes) (ascii3 ++ ascii2)
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
ascii2codes = ["BS","HT","LF","VT","FF","CR","SO","SI","EM",
"FS","GS","RS","US","SP"]
ascii3codes = ["NUL","SOH","STX","ETX","EOT","ENQ","ACK","BEL",
"DLE","DC1","DC2","DC3","DC4","NAK","SYN","ETB",
"CAN","SUB","ESC","DEL"]
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
ascii2 = "\b\t\n\v\f\r\SO\SI\EM\FS\GS\RS\US "
ascii3 = "\NUL\SOH\STX\ETX\EOT\ENQ\ACK\a\DLE\DC1\DC2\DC3\DC4\NAK\SYN\ETB\CAN\SUB\ESC\DEL"
2015-07-30 18:45:06 +03:00
2015-08-12 20:51:06 +03:00
-- numbers — integers
2015-07-30 18:45:06 +03:00
integer = decimal
2015-08-12 20:51:06 +03:00
integer' = signed integer
2015-07-30 18:45:06 +03:00
decimal = lexeme (nump "" digitChar <?> "integer")
2015-08-12 20:51:06 +03:00
hexadecimal = lexeme $ char '0' >> oneOf "xX" >> nump "0x" hexDigitChar
octal = lexeme $ char '0' >> oneOf "oO" >> nump "0o" octDigitChar
2015-07-30 18:45:06 +03:00
2015-08-12 20:51:06 +03:00
nump prefix baseDigit = read . (prefix ++) <$> some baseDigit
2015-07-30 18:45:06 +03:00
2015-08-12 20:51:06 +03:00
signed p = ($) <$> option id (lexeme sign) <*> p
2015-07-30 18:45:06 +03:00
2015-08-12 20:51:06 +03:00
sign :: (Stream s m Char, Num a) => ParsecT s u m (a -> a)
sign = (char '+' *> return id) <|> (char '-' *> return negate)
2015-07-30 18:45:06 +03:00
2015-08-12 20:51:06 +03:00
-- numbers — floats
2008-01-13 20:53:15 +03:00
2015-08-12 20:51:06 +03:00
float = lexeme ffloat <?> "float"
float' = signed float
ffloat = read <$> ffloat'
where
ffloat' = do
decimal <- fDec
rest <- fraction <|> fExp
return $ decimal ++ rest
fraction = do
void $ char '.'
decimal <- fDec
exp <- option "" fExp
return $ '.' : decimal ++ exp
fDec = some digitChar
fExp = do
expChar <- oneOf "eE"
signStr <- option "" (pure <$> oneOf "+-")
decimal <- fDec
return $ expChar : signStr ++ decimal
-- numbers — a more general case
number = (Right <$> try float) <|> (Left <$> integer) <?> "number"
number' = (Right <$> try float') <|> (Left <$> integer') <?> "number"
-- operators & reserved ops
reservedOp name =
lexeme $ try $ do
void $ string name
notFollowedBy (opLetter languageDef) <?> ("end of " ++ show name)
operator =
lexeme $ try $ do
name <- oper
if isReservedOp name
then unexpected ("reserved operator " ++ show name)
else return name
oper = ((:) <$> opStart languageDef <*> many (opLetter languageDef))
<?> "operator"
isReservedOp = isReserved . sort $ reservedOpNames languageDef
-- identifiers & reserved words
reserved name =
lexeme $ try $ do
void $ caseString name
notFollowedBy (identLetter languageDef) <?> ("end of " ++ show name)
caseString name
| caseSensitive languageDef = string name
| otherwise = walk name >> return name
where walk = foldr (\c -> ((caseChar c <?> show name) >>)) (return ())
caseChar c
| isAlpha c = char (toLower c) <|> char (toUpper c)
| otherwise = char c
identifier =
lexeme $ try $ do
name <- ident
if isReservedName name
then unexpected ("reserved word " ++ show name)
else return name
ident = ((:) <$> identStart languageDef <*> many (identLetter languageDef))
<?> "identifier"
isReservedName name = isReserved theReservedNames caseName
where caseName
| caseSensitive languageDef = name
| otherwise = toLower <$> name
isReserved names name = scan names
where scan [] = False
scan (r:rs) = case compare r name of
LT -> scan rs
EQ -> True
GT -> False
theReservedNames
| caseSensitive languageDef = sort reserved
| otherwise = sort . fmap (fmap toLower) $ reserved
where reserved = reservedNames languageDef
-- white space & symbols
symbol = lexeme . string
lexeme p = p <* whiteSpace
whiteSpace = hidden space -- FIXME: write it in a decent manner
-- \| noLine && noMulti = skipMany (space <?> "")
-- \| noLine = skipMany (space <|>
-- multiLineComment <?> "")
-- \| noMulti = skipMany (space <|>
-- oneLineComment <?> "")
-- \| otherwise = skipMany (space <|>
-- oneLineComment <|>
-- multiLineComment <?> "")
-- where
-- noLine = null (commentLine languageDef)
-- noMulti = null (commentStart languageDef)
-- oneLineComment = void (try (string (commentLine languageDef))
-- >> skipMany (satisfy (/= '\n')))
-- multiLineComment = try (string (commentStart languageDef)) >> inComment
-- inComment = if nestedComments languageDef
-- then inCommentMulti
-- else inCommentSingle
-- inCommentMulti
-- = void (try . string $ commentEnd languageDef)
-- <|> (multiLineComment >> inCommentMulti)
-- <|> (skipSome (noneOf startEnd) >> inCommentMulti)
-- <|> (oneOf startEnd >> inCommentMulti)
-- <?> "end of comment"
-- inCommentSingle
-- = void (try . string $ commentEnd languageDef)
-- <|> (skipSome (noneOf startEnd) >> inCommentSingle)
-- <|> (oneOf startEnd >> inCommentSingle)
-- <?> "end of comment"
-- startEnd = nub $ (++) <$> commentEnd <*> commentStart $ languageDef