module Compiler.Lexer.Keywords where import Common import Compiler.Lexer.Whitespaces import Control.Applicative import Control.Monad import Parser import Test.Common data Keyword = KwFor | KwEndFor | KwForEach | KwAs | KwEndForEach | KwBreak | KwWhile | KwEndWhile | KwLet | KwIf | KwEndFn | KwThen | KwElseIf | KwElse | KwEndIf | KwProc | KwLoop | KwEndLoop | KwEndProc | KwTo | KwReturn | KwAssignment | KwFn -- We don't want to generate this in automatic tests because of the lookahead for ( deriving (Show, Lift,Eq, Enum, Bounded) instance HasParser Keyword where parser = parseFor KwForEach <|> parseFor KwEndForEach <|> parseFor KwFor <|> parseFor KwAs <|> parseFor KwEndFor <|> parseFor KwWhile <|> parseFor KwBreak <|> parseFor KwEndWhile <|> parseFor KwLet <|> parseFor KwIf <|> parseFor KwFn <|> parseFor KwEndFn <|> parseFor KwThen <|> parseFor KwElseIf <|> parseFor KwElse <|> parseFor KwEndIf <|> parseFor KwProc <|> parseFor KwLoop <|> parseFor KwEndLoop <|> parseFor KwEndProc <|> parseFor KwTo <|> parseFor KwReturn <|> parseFor KwAssignment where parseFor :: Keyword -> Parser Keyword parseFor kw = do pkw <- parseAndReturn (toSource kw) kw case pkw of KwAssignment -> pure pkw KwFn -> do lookAhead ((void $ do void $ many (parser @Whitespace) pText "(")) >>= \case Just _ -> pure pkw Nothing -> cantHandle KwEndFn -> pure pkw _ -> do lookAhead ((void $ parser @Whitespace) <|> eof) >>= \case Just _ -> pure pkw Nothing -> cantHandle instance ToSource Keyword where toSource = \case KwFor -> "for" KwEndFor -> "endfor" KwForEach -> "foreach" KwAs -> "as" KwEndForEach -> "endforeach" KwBreak -> "break" KwWhile -> "while" KwEndWhile -> "endwhile" KwLet -> "let" KwIf -> "if" KwFn -> "fn" KwEndFn -> "endfn" KwThen -> "then" KwElseIf -> "elseif" KwElse -> "else" KwEndIf -> "endif" KwProc -> "proc" KwLoop -> "loop" KwEndProc -> "endproc" KwEndLoop -> "endloop" KwTo -> "to" KwReturn -> "return" KwAssignment -> "=" instance HasGen Keyword where getGen = enum KwFor KwAssignment