The Parser a type represents a parsing function that consumes some input string, potentially producing a value of type a along with the remaining unparsed portion of the string.
When a parser is run:
If parsing succeeds, it returns Just (result, remainingInput) where result is the parsed value and remainingInput is the unconsumed portion of the input
If parsing fails, it returns Nothing
This approach allows parsers to be composed sequentially and makes backtracking possible through the use of the Maybe monad.
(b) Implement the 'char' parser that consumes a specific character
Answer
char :: Char -> Parser Charchar c = Parser $ \input -> case input of (x:xs) | x == c -> Just (c, xs) _ -> Nothing
The char function creates a parser that succeeds only if the first character of the input matches the expected character c. If successful, it returns that character and the remaining input.
(c) Implement the alternative (<|>) combinator that tries the second parser if the first fails.
Answer
(<|>) :: Parser a -> Parser a -> Parser ap1 <|> p2 = Parser $ \input -> case runParser p1 input of Nothing -> runParser p2 input success -> success
The alternative combinator tries the first parser on the input. If it succeeds, that result is used. If it fails, the second parser is tried on the same input.
(a) Implement the many and some parser combinators, which parse zero or more, and one or more occurrences of a pattern respectively.
Answer
many :: Parser a -> Parser [a]many p = some p <|> return []some :: Parser a -> Parser [a]some p = do x <- p xs <- many p return (x:xs)
The many combinator tries to apply the parser repeatedly, collecting all results into a list. It succeeds even if the parser never succeeds (returning an empty list).
The some combinator is similar but requires at least one successful parse of the pattern.
(b) Implement a parser for floating-point numbers of the form 123.456. Your parser should handle both the integer and fractional parts.
Answer
import Control.Applicative ((<|>))digit :: Parser Chardigit = Parser $ \input -> case input of (x:xs) | isDigit x -> Just (x, xs) _ -> Nothingdigits :: Parser Stringdigits = some digitfloat :: Parser Doublefloat = do intPart <- digits char '.' fracPart <- digits return $ read (intPart ++ "." ++ fracPart)-- Alternative implementationfloat' :: Parser Doublefloat' = do intPart <- digits fracPart <- option 0 $ do char '.' fracs <- digits return $ read fracs / (10 ^ length fracs) return $ read intPart + fracPartoption :: a -> Parser a -> Parser aoption x p = p <|> return x
This parser handles floating-point numbers by parsing the integer part, the decimal point, and the fractional part separately, then combining them.
Implement a parser for the JArray constructor, which parses arrays of the form [value1, value2, ...].
Answer
-- Assuming we already have parsers for simpler JSON valuesjValue :: Parser JValuejValue = jString <|> jNumber <|> jBool <|> jNull <|> jArray <|> jObjectjArray :: Parser JValuejArray = do char '[' whitespace values <- sepBy jValue (char ',' >> whitespace) whitespace char ']' return $ JArray values-- Helper combinatorswhitespace :: Parser ()whitespace = do many (satisfy isSpace) return ()sepBy :: Parser a -> Parser b -> Parser [a]sepBy p sep = sepBy1 p sep <|> return []sepBy1 :: Parser a -> Parser b -> Parser [a]sepBy1 p sep = do x <- p xs <- many (sep >> p) return (x:xs)satisfy :: (Char -> Bool) -> Parser Charsatisfy pred = Parser $ \input -> case input of (x:xs) | pred x -> Just (x, xs) _ -> Nothing
This parser handles JSON arrays by parsing the opening bracket, followed by a list of values separated by commas, then the closing bracket.
(d) Recursive descent parsers often need to handle left-recursion carefully. Consider a simple expression grammar for addition:
expr ::= expr "+" term | term
term ::= NUMBER
This is left-recursive and will cause infinite recursion in a naive implementation. Rewrite this grammar to eliminate left-recursion, then implement the parser.
Answer
First, we rewrite the grammar to eliminate left-recursion:
expr ::= term expr'
expr' ::= "+" term expr' | ε
term ::= NUMBER
Now we can implement the parser:
expr :: Parser Intexpr = do t <- term exprRest texprRest :: Int -> Parser IntexprRest left = (do char '+' t <- term exprRest (left + t) ) <|> return leftterm :: Parser Intterm = do digits <- some digit return $ read digits
This implementation avoids left-recursion by parsing a term first, then handling any subsequent ”+” operations iteratively through the exprRest function.
(e) Implement a parser combinator chainl1 that parses left-associative expressions with a given operator.
chainl1 :: Parser a -> Parser (a -> a -> a) -> Parser a
Then use it to implement a simple calculator supporting addition, subtraction, multiplication, and division with the correct operator precedence.
Answer
chainl1 :: Parser a -> Parser (a -> a -> a) -> Parser achainl1 p op = do x <- p rest x where rest x = (do f <- op y <- p rest (f x y) ) <|> return x-- Calculator implementationexpr :: Parser Intexpr = term `chainl1` addOp where addOp = (char '+' >> return (+)) <|> (char '-' >> return (-))term :: Parser Intterm = factor `chainl1` mulOp where mulOp = (char '*' >> return (*)) <|> (char '/' >> return div)factor :: Parser Intfactor = do char '(' x <- expr char ')' return x <|> do digits <- some digit return $ read digitscalculator :: String -> Maybe Intcalculator input = case runParser expr input of Just (result, "") -> Just result _ -> Nothing
The chainl1 combinator implements left-associative parsing of operators. The calculator uses this to create a proper precedence hierarchy: factors (numbers or parenthesized expressions), terms (multiplication/division), and expressions (addition/subtraction).
(f) Monadic parsers allow for context-sensitive parsing. Implement a parser for balanced parentheses that keeps track of the nesting depth.
Answer
-- The State monad is used to track nesting depthtype ParserState = Int -- Current nesting depthbalancedParens :: Parser StringbalancedParens = evalStateT balancedParens' 0 where balancedParens' :: StateT ParserState Parser String balancedParens' = do lift (eof) >>= \case True -> do depth <- get if depth == 0 then return "" else fail "Unbalanced parentheses: too many opening parentheses" False -> do c <- lift anyChar case c of '(' -> do modify (+1) rest <- balancedParens' return ('(':rest) ')' -> do depth <- get if depth > 0 then do modify (subtract 1) rest <- balancedParens' return (')':rest) else fail "Unbalanced parentheses: too many closing parentheses" _ -> do rest <- balancedParens' return (c:rest) eof :: Parser Bool eof = Parser $ \input -> case input of [] -> Just (True, []) _ -> Just (False, input) anyChar :: Parser Char anyChar = Parser $ \input -> case input of (x:xs) -> Just (x, xs) [] -> Nothing
This parser keeps track of the nesting depth of parentheses using a state monad transformer on top of the parser monad. It increments the depth for each opening parenthesis and decrements it for each closing one, failing if a closing parenthesis appears without a matching opening one or if the input ends with unclosed parentheses.
(g) Implement a parser for simple arithmetic expressions that supports variables. The parser should build an abstract syntax tree (AST) that can be evaluated with a given environment of variable values.
Answer
-- AST definitiondata Expr = Lit Int | Var String | Add Expr Expr | Sub Expr Expr | Mul Expr Expr | Div Expr Expr deriving (Show)type Env = [(String, Int)]-- Evaluatoreval :: Env -> Expr -> Inteval _ (Lit n) = neval env (Var name) = case lookup name env of Just val -> val Nothing -> error $ "Undefined variable: " ++ nameeval env (Add e1 e2) = eval env e1 + eval env e2eval env (Sub e1 e2) = eval env e1 - eval env e2eval env (Mul e1 e2) = eval env e1 * eval env e2eval env (Div e1 e2) = eval env e1 `div` eval env e2-- Parserexpr :: Parser Exprexpr = term `chainl1` addOp where addOp = (char '+' >> return Add) <|> (char '-' >> return Sub)term :: Parser Exprterm = factor `chainl1` mulOp where mulOp = (char '*' >> return Mul) <|> (char '/' >> return Div)factor :: Parser Exprfactor = do char '(' x <- expr char ')' return x <|> literal <|> variableliteral :: Parser Exprliteral = do digits <- some digit return $ Lit (read digits)variable :: Parser Exprvariable = do first <- satisfy isAlpha rest <- many (satisfy (\c -> isAlphaNum c || c == '_')) return $ Var (first:rest)-- UsageparseExpr :: String -> Maybe ExprparseExpr input = case runParser expr input of Just (result, "") -> Just result _ -> NothingevaluateExpr :: Env -> String -> Maybe IntevaluateExpr env input = eval env <$> parseExpr input
This implementation creates a parser that builds an abstract syntax tree (AST) for arithmetic expressions that can include variables. The AST can then be evaluated with a given environment that maps variable names to values.
Monad Transformers
(a) What are monad transformers and why are they useful in functional programming?
Answer
Monad transformers are type constructors that take a monad as an argument and return a monad as a result. They allow multiple monadic effects to be combined into a single monad.
They’re useful because:
They allow composition of different monadic effects (e.g., state, errors, IO)
They avoid nested monadic binds when using multiple monads
They provide a structured way to lift operations from the base monad
They maintain type safety while working with complex effects
Without monad transformers, working with multiple monads would require excessive unwrapping and rewrapping of monadic values.
(b) Define the StateT monad transformer and its Monad instance.
Answer
newtype StateT s m a = StateT { runStateT :: s -> m (a, s) }instance (Monad m) => Monad (StateT s m) where return a = StateT $ \s -> return (a, s) m >>= f = StateT $ \s -> do (a, s') <- runStateT m s runStateT (f a) s'
The StateT transformer adds state to an existing monad. The return function wraps a value with its state. The bind operator sequences two stateful computations by running the first, then passing both its result and the updated state to the second.
(c) Implement the following functions for the StateT monad transformer:
get :: Monad m => StateT s m sput :: Monad m => s -> StateT s m ()modify :: Monad m => (s -> s) -> StateT s m ()
Answer
get :: Monad m => StateT s m sget = StateT $ \s -> return (s, s)put :: Monad m => s -> StateT s m ()put s = StateT $ \_ -> return ((), s)modify :: Monad m => (s -> s) -> StateT s m ()modify f = StateT $ \s -> return ((), f s)
get returns the current state as its result value
put replaces the current state with a new state
modify applies a function to transform the current state
Equational Reasoning
(a) Consider the following Haskell function:
map f (filter p xs) = filter p (map f xs)
Is this equation always true? Prove your answer using equational reasoning.
Answer
This equation is not always true.
Let’s use equational reasoning:
For the left-hand side:
map f (filter p xs)
= map f [x | x <- xs, p x]
= [f x | x <- xs, p x]
For the right-hand side:
filter p (map f xs)
= filter p [f x | x <- xs]
= [f x | x <- xs, p (f x)]
These are only equal when p x ⟺ p (f x) for all x in xs, which isn’t true in general.
For a counterexample, let:
f = (*2)
p = even
xs = [1,2,3]
Then:
map f (filter p xs) = map f [2] = [4]
filter p (map f xs) = filter p [2,4,6] = [2,4,6]
(b) Using equational reasoning, prove that foldr f z (xs ++ ys) = foldr f (foldr f z ys) xs for any function f, value z, and lists xs and ys.
Answer
We’ll prove this by induction on the structure of xs.
Base case: xs = []
foldr f z ([] ++ ys)
= foldr f z ys -- definition of (++)
= foldr f (foldr f z ys) [] -- definition of foldr with empty list
Inductive case: Assume it holds for some list xs, prove for (x:xs).
foldr f z ((x:xs) ++ ys)
= foldr f z (x:(xs ++ ys)) -- definition of (++)
= f x (foldr f z (xs ++ ys)) -- definition of foldr
= f x (foldr f (foldr f z ys) xs) -- inductive hypothesis
= foldr f (foldr f z ys) (x:xs) -- definition of foldr
Therefore, by induction, the property holds for all lists xs and ys.
Lambda Calculus (Extended Examples)
(a) Convert the following lambda expressions to their equivalent Haskell functions:
λx.λy. x y x
λf.λg.λx. f (g x)
λf.λg.λx. f x (g x)
Answer
-- λx.λy. x y xfunc1 :: (b -> a -> c) -> b -> a -> cfunc1 x y = x y x-- λf.λg.λx. f (g x)func2 :: (b -> c) -> (a -> b) -> a -> cfunc2 f g x = f (g x)-- This is function composition: func2 f g = f . g-- λf.λg.λx. f x (g x)func3 :: (a -> b -> c) -> (a -> b) -> a -> cfunc3 f g x = f x (g x)
Note that func2 is the standard function composition operator (.) in Haskell, while func3 is a special kind of composition sometimes called the S-combinator.
(b) Encode the following concepts in the untyped lambda calculus:
Boolean values TRUE and FALSE, and the IF-THEN-ELSE construct
Implement the logical AND operation using these encodings
Answer
Boolean encodings:
TRUE = λx.λy.x -- Takes two arguments and returns the first
FALSE = λx.λy.y -- Takes two arguments and returns the second
IF = λp.λt.λf.p t f -- If p then t else f
In Haskell syntax:
true :: a -> b -> atrue x _ = xfalse :: a -> b -> bfalse _ y = yifThenElse :: (a -> b -> c) -> a -> b -> cifThenElse p t f = p t f
Logical AND:
AND = λp.λq.p q p -- If p then q else p (which is FALSE)
-- or alternatively:
AND = λp.λq.p q FALSE -- If p then q else FALSE
In Haskell:
and :: (a -> b -> a) -> (a -> b -> a) -> a -> b -> aand p q = p q p-- or:and p q = p q false
This works because if p is TRUE, then the result is q; if p is FALSE, the result is FALSE.