-- | Parsing -- Examples to illustrate how to write parsers using parsing combinators -- Functional Programming course 2017. -- Thomas Hallgren {- This started as a skeleton, the definitions were filled in during the lecture. -} module ParsingExamples where import Data.Char(isDigit) import Parsing hiding (chain,digit) import Control.Monad(forever) -------------------------------------------------------------------------------- -- * A first example -- Writing a recursive decent parser directly -- Using functions of type String -> Maybe (a,String) {- BNF: digit = "0".."9". number = digit{digit}. addition = number "+" number. -} number_v1 :: String -> Maybe (Integer,String) number_v1 s = case span isDigit s of ([],_) -> Nothing (ds,r) -> Just (read ds,r) addition_v1 :: String -> Maybe (Integer,String) addition_v1 s = case number_v1 s of Just (n1,'+':r) -> case number_v1 r of Just (n2,r') -> Just (n1+n2,r') _ -> Nothing _ -> Nothing {- A small extension to the BNF multiplication ::= number "*" number. calculation ::= addition | multiplication. -} multiplication_v1 :: String -> Maybe (Integer,String) multiplication_v1 s = case number_v1 s of Just (n1,'*':r) -> case number_v1 r of Just (n2,r') -> Just (n1*n2,r') _ -> Nothing _ -> Nothing calculation_v1 :: String -> Maybe (Integer,String) calculation_v1 s = case addition_v1 s of Nothing -> multiplication_v1 s result -> result -------------------------------------------------------------------------------- -- * Rewriting our first example using parsing combinators -- | Parse a digit (also available in the Parsing module) digit :: Parser Char digit = sat isDigit -- | Parse a number number :: Parser Integer number = do ds <- oneOrMore digit return (read ds) -- | Parse two numbers, separated by +, and add them addition :: Parser Integer addition = do n1 <- number char '+' n2 <- number return (n1+n2) -- | Parse two numbers, separated by *, and multiply them multiplication :: Parser Integer multiplication = do n1 <- number char '*' n2 <- number return (n1*n2) calculation :: Parser Integer calculation = addition <|> multiplication -------------------------------------------------------------------------------- -- * An expression parser (version 1) data Expr = Num Integer | Add Expr Expr | Mul Expr Expr deriving (Eq,Show) eval :: Expr -> Integer eval (Num n) = n eval (Add a b) = eval a + eval b eval (Mul a b) = eval a * eval b {- EBNF: expr ::= term {"+" term}. term ::= factor {"*" factor}. factor ::= number | "(" expr ")". -} {- expr, term, factor :: Parser Expr expr = do t <- term ts <- zeroOrMore (do char '+'; term) return (foldl Add t ts) term = do t <- factor ts <- zeroOrMore (do char '*'; factor) return (foldl Mul t ts) factor = do n <- number return (Num n) <|> do char '(' e <- expr char ')' return e --} -------------------------------------------------------------------------------- -- * A more elegant expression parser --{- expr, term, factor :: Parser Expr expr = leftAssoc Add term (char '+') term = leftAssoc Mul factor (char '*') factor = (Num <$> number) <|> (char '(' *> expr <* char ')') --} -- | Parse a list of items with separators -- (also available in the Parsing module) chain :: Parser item -> Parser sep -> Parser [item] chain item sep = do i <- item is <- zeroOrMore (do sep; item) return (i:is) -- | A parser for left-associative operators leftAssoc :: (t->t->t) -> Parser t -> Parser sep -> Parser t leftAssoc op item sep = foldl1 op <$> chain item sep rightAssoc op item sep = undefined -- exercise -------------------------------------------------------------------------------- -- * The simple calculator example (filled in after the lecture) main = do putStrLn "Welcome to the simple calculator!" forever readEvalPrint readEvalPrint = do putStr "Expression? " s <- getLine case parse expr s of Just (e,"") -> print (eval e) _ -> putStrLn "Syntax error!" -------------------------------------------------------------------------------- -- * More examples -- ** Data types with infix operatos infixl 6 :+ infixl 7 :* data Expr2 = C Integer | Expr2 :+ Expr2 | Expr2 :* Expr2 deriving (Show,Read) -- gives us almost what we want ex1 = C 2 ex2 = ex1 :+ ex1 ex3 = C 1 :+ C 2 :* C 3 ex4 = (C 1 :+ C 2) :* C 3 -- | Parse a specific sequence of characters string :: String -> Parser String string "" = return "" string (c:s) = do c' <- char c s' <- string s return (c':s') {- Below are the tests we ran in GHCi: :t takeWhile :t span :t read :l ParsingExamples.hs :t number_v1 number_v1 "42" number_v1 "42kaljshdf" number_v1 "" number_v1 "alksjhdf42" :r addition_v1 "3+4" addition_v1 "3+4ksdjhf" addition_v1 "3+" addition_v1 "+3" addition_v1 "4+3" addition_v1 "4 + 3" addition_v1 "4+3+5" :r calculation_v1 "3+4" calculation_v1 "3*4" calculation_v1 "3*4asfd" calculation_v1 "3x*4" calculation_v1 "100000000000*3" :r :t calculation :t parse calculation parse calculation "3+4" parse calculation "3*4" parse calculation "3*4asd" calculation_v1 "3*4asd" :t parse :t foldr :t foldl :r :t expr parse expr "1+2*3" parse expr "1+2*3+4" parse expr "(1+2)*3" :t foldl1 foldl1 Add [Num 1] foldl1 Add [Num 1,Num 2] foldl1 Add [Num 1,Num 2,Num 3] :r parse expr "(1+2)*3" parse expr "1+2*3" :r parse expr "1+2*3" :r main -}