simple-arithmetic-compiler/app/Parser.hs

39 lines
1,004 B
Haskell

module Parser where
import qualified Lexer as L
import Control.Applicative as Applicative
type AST = Expr
data Expr = Add Term Expr
| Sub Term Expr
| ETerm Term
deriving Show
data Term = Mult Factor Term
| Div Factor Term
| TFactor Factor
deriving Show
data Factor = Integer Int
| Parantheses Expr
| NegFactor Factor
deriving Show
type Tokens = [L.Token]
newtype Parser a = Parser {
runParser :: Tokens -> Maybe (Tokens, a)
}
instance Functor Parser where
fmap f (Parser p) = Parser $ \input -> case p input of
Nothing -> Nothing
Just (rest, a) -> Just (rest, f a)
instance Applicative Parser where
pure x = Parser $ \input -> Just (input, x)
(<*>) (Parser fParser) (Parser a) = Parser $ \input -> case fParser input of
Nothing -> Nothing
Just (rest, f) -> case a rest of
Nothing -> Nothing
Just (rest', x) -> Just (rest', f x)