Implement Parsing for Tokens of AST
This commit is contained in:
parent
39d77eafe0
commit
9d1a80bf2b
2 changed files with 51 additions and 1 deletions
|
|
@ -7,7 +7,7 @@ data Token = Plus
|
||||||
| Integer Int
|
| Integer Int
|
||||||
| LBrace
|
| LBrace
|
||||||
| RBrace
|
| RBrace
|
||||||
deriving Show
|
deriving (Eq, Show)
|
||||||
|
|
||||||
lex :: String -> [Token]
|
lex :: String -> [Token]
|
||||||
lex source = reverse (lex' source [] (length source))
|
lex source = reverse (lex' source [] (length source))
|
||||||
|
|
|
||||||
|
|
@ -2,6 +2,7 @@ module Parser where
|
||||||
|
|
||||||
import qualified Lexer as L
|
import qualified Lexer as L
|
||||||
import Control.Applicative as Applicative
|
import Control.Applicative as Applicative
|
||||||
|
import Data.Void as Void
|
||||||
|
|
||||||
type AST = Expr
|
type AST = Expr
|
||||||
|
|
||||||
|
|
@ -43,3 +44,52 @@ instance Alternative Parser where
|
||||||
(<|>) (Parser p1) (Parser p2) = Parser $ \input -> case p1 input of
|
(<|>) (Parser p1) (Parser p2) = Parser $ \input -> case p1 input of
|
||||||
Nothing -> p2 input
|
Nothing -> p2 input
|
||||||
result -> result
|
result -> result
|
||||||
|
|
||||||
|
|
||||||
|
parseAdd :: Parser Expr
|
||||||
|
parseAdd = liftA2 Add (parseTerm <* expect L.Plus) parseExpression
|
||||||
|
|
||||||
|
parseSub :: Parser Expr
|
||||||
|
parseSub = liftA2 Sub (parseTerm <* expect L.Hyphen) parseExpression
|
||||||
|
|
||||||
|
parseETerm :: Parser Expr
|
||||||
|
parseETerm = ETerm <$> parseTerm
|
||||||
|
|
||||||
|
parseExpression :: Parser Expr
|
||||||
|
parseExpression = parseAdd <|> parseSub <|> parseETerm
|
||||||
|
|
||||||
|
|
||||||
|
parseMult :: Parser Term
|
||||||
|
parseMult = liftA2 Mult (parseFactor <* expect L.Asterisk) parseTerm
|
||||||
|
|
||||||
|
parseDiv :: Parser Term
|
||||||
|
parseDiv = liftA2 Div (parseFactor <* expect L.ForwardSlash) parseTerm
|
||||||
|
|
||||||
|
parseTFactor :: Parser Term
|
||||||
|
parseTFactor = TFactor <$> parseFactor
|
||||||
|
|
||||||
|
parseTerm :: Parser Term
|
||||||
|
parseTerm = parseMult <|> parseDiv <|> parseTFactor
|
||||||
|
|
||||||
|
|
||||||
|
parseFactor :: Parser Factor
|
||||||
|
parseFactor = parseInt <|> parseParatheses <|> parseNegFactor
|
||||||
|
|
||||||
|
parseInt :: Parser Factor
|
||||||
|
parseInt = Parser $ \(token:rest) -> case token of
|
||||||
|
L.Integer i -> Just (rest, Integer i)
|
||||||
|
_ -> Nothing
|
||||||
|
|
||||||
|
parseNegFactor :: Parser Factor
|
||||||
|
parseNegFactor = NegFactor <$> (expect L.Hyphen *> parseFactor)
|
||||||
|
|
||||||
|
parseParatheses :: Parser Factor
|
||||||
|
parseParatheses = Parantheses <$> (expect L.LBrace *> parseExpression <* expect L.RBrace)
|
||||||
|
|
||||||
|
|
||||||
|
expect :: L.Token -> Parser (Maybe Void)
|
||||||
|
expect token = Parser $ \stream -> case stream of
|
||||||
|
(t:rest) -> if t == token
|
||||||
|
then Just (rest, Nothing)
|
||||||
|
else Nothing
|
||||||
|
_ -> Nothing
|
||||||
|
|
|
||||||
Loading…
Add table
Add a link
Reference in a new issue