CSE230 Fa16 - Homework #2, Due Friday 10/28/16



> {-# LANGUAGE TypeSynonymInstances #-}
> module Hw2 where
> import Control.Applicative hiding (empty, (<|>))
> import Data.Map
> import Control.Monad.State hiding (when)
> import Text.Parsec hiding (State, between)
> import Text.Parsec.Combinator hiding (between)
> import Text.Parsec.Char
> import Text.Parsec.String

To complete this homework,

  1. download Hw2.tar.gz,
  2. unzip it by tar -zxvf Hw2.tar.gz
  3. cd Hw2 ,
  4. Fill in each error "TBD" in src/Hw2.hs
  5. Submit by mailing the completed Hw2.hs to cse230@goto.ucsd.edu with the subject “HW2”.

You will receive a confirmation email after submitting.

Your code must typecheck against the given type signatures. Feel free to add your own tests to this file to exercise the functions you write. As before, you can compile the code by doing stack build and load in ghci by doing stack ghci.

Problem 0: All About You

Tell us your name, email and student ID, by replacing the respective strings below

> myName  = "Write Your Name  Here"
> myEmail = "Write Your Email Here"
> mySID   = "Write Your SID   Here"

Problem 1: All About foldl

Define the following functions by filling in the “error” portion:

  1. Describe foldl and give an implementation:
> myFoldl :: (a -> b -> a) -> a -> [b] -> a
> myFoldl f b xs = error "TBD"
  1. Using the standard foldl (not myFoldl), define the list reverse function:
> myReverse :: [a] -> [a]
> myReverse xs = error "TBD"
  1. Define foldr in terms of foldl:
> myFoldr :: (a -> b -> b) -> b -> [a] -> b
> myFoldr f b xs = error "TBD"
  1. Define foldl in terms of the standard foldr (not myFoldr):
> myFoldl2 :: (a -> b -> a) -> a -> [b] -> a
> myFoldl2 f b xs = error "TBD"
  1. Try applying foldl to a gigantic list. Why is it so slow? Try using foldl' (from Data.List) instead; can you explain why it’s faster?

Part 2: Binary Search Trees

Recall the following type of binary search trees:

> data BST k v = Emp 
>              | Bind k v (BST k v) (BST k v) 
>              deriving (Show)

Define a delete function for BSTs of this type:

> delete :: (Ord k) => k -> BST k v -> BST k v
> delete k t = error "TBD"

Part 3: An Interpreter for WHILE

Next, you will use monads to build an evaluator for a simple WHILE language. In this language, we will represent different program variables as

> type Variable = String

Programs in the language are simply values of the type

> data Statement =
>     Assign Variable Expression          -- x = e
>   | If Expression Statement Statement   -- if (e) {s1} else {s2}
>   | While Expression Statement          -- while (e) {s}
>   | Sequence Statement Statement        -- s1; s2
>   | Skip                                -- no-op
>   deriving (Show)

where expressions are variables, constants or binary operators applied to sub-expressions

> data Expression =
>     Var Variable                        -- x
>   | Val Value                           -- v 
>   | Op  Bop Expression Expression
>   deriving (Show)

and binary operators are simply two-ary functions

> data Bop = 
>     Plus     -- (+)  :: Int  -> Int  -> Int
>   | Minus    -- (-)  :: Int  -> Int  -> Int
>   | Times    -- (*)  :: Int  -> Int  -> Int
>   | Divide   -- (/)  :: Int  -> Int  -> Int
>   | Gt       -- (>)  :: Int -> Int -> Bool 
>   | Ge       -- (>=) :: Int -> Int -> Bool
>   | Lt       -- (<)  :: Int -> Int -> Bool
>   | Le       -- (<=) :: Int -> Int -> Bool
>   deriving (Show)
> data Value =
>     IntVal Int
>   | BoolVal Bool
>   deriving (Show)

We will represent the store i.e. the machine’s memory, as an associative map from Variable to Value

> type Store = Map Variable Value

Note: we don’t have exceptions (yet), so if a variable is not found (eg because it is not initialized) simply return the value 0. In future assignments, we will add this as a case where exceptions are thrown (the other case being type errors.)

We will use the standard library’s State monad to represent the world-transformer. Intuitively, State s a is equivalent to the world-transformer s -> (a, s). See the above documentation for more details. You can ignore the bits about StateT for now.

Expression Evaluator

First, write a function

> evalE :: Expression -> State Store Value

that takes as input an expression and returns a world-transformer that returns a value. Yes, right now, the transformer doesnt really transform the world, but we will use the monad nevertheless as later, the world may change, when we add exceptions and such.

Hint: The value get is of type State Store Store. Thus, to extract the value of the “current store” in a variable s use s <- get.

> evalOp :: Bop -> Value -> Value -> Value
> evalOp Plus (IntVal i) (IntVal j) = IntVal (i+j)
> 
> evalE (Var x)      = error "TBD"
> evalE (Val v)      = error "TBD"
> evalE (Op o e1 e2) = error "TBD"

Statement Evaluator

Next, write a function

> evalS :: Statement -> State Store ()

that takes as input a statement and returns a world-transformer that returns a unit. Here, the world-transformer should in fact update the input store appropriately with the assignments executed in the course of evaluating the Statement.

Hint: The value put is of type Store -> State Store (). Thus, to “update” the value of the store with the new store s' do put s'.

> evalS (Assign x e )    = error "TBD" 
> evalS w@(While e s)    = error "TBD" 
> evalS Skip             = error "TBD"
> evalS (Sequence s1 s2) = error "TBD"
> evalS (If e s1 s2)     = error "TBD" 

In the If case, if e evaluates to a non-boolean value, just skip both the branches. (We will convert it into a type error in the next homework.) Finally, write a function

> execS :: Statement -> Store -> Store
> execS = error "TBD"

such that execS stmt store returns the new Store that results from evaluating the command stmt from the world store. Hint: You may want to use the library function

execState :: State s a -> s -> s

When you are done with the above, the following function will “run” a statement starting with the empty store (where no variable is initialized). Running the program should print the value of all variables at the end of execution.

> run :: Statement -> IO ()
> run stmt = do putStrLn "Output Store:" 
>               putStrLn $ show $ execS stmt empty

Here are a few “tests” that you can use to check your implementation.

> w_test = (Sequence (Assign "X" (Op Plus (Op Minus (Op Plus (Val (IntVal 1)) (Val (IntVal 2))) (Val (IntVal 3))) (Op Plus (Val (IntVal 1)) (Val (IntVal 3))))) (Sequence (Assign "Y" (Val (IntVal 0))) (While (Op Gt (Var "X") (Val (IntVal 0))) (Sequence (Assign "Y" (Op Plus (Var "Y") (Var "X"))) (Assign "X" (Op Minus (Var "X") (Val (IntVal 1))))))))
> w_fact = (Sequence (Assign "N" (Val (IntVal 2))) (Sequence (Assign "F" (Val (IntVal 1))) (While (Op Gt (Var "N") (Val (IntVal 0))) (Sequence (Assign "X" (Var "N")) (Sequence (Assign "Z" (Var "F")) (Sequence (While (Op Gt (Var "X") (Val (IntVal 1))) (Sequence (Assign "F" (Op Plus (Var "Z") (Var "F"))) (Assign "X" (Op Minus (Var "X") (Val (IntVal 1)))))) (Assign "N" (Op Minus (Var "N") (Val (IntVal 1))))))))))

As you can see, it is rather tedious to write the above tests! They correspond to the code in the files tests/test.imp and tests/fact.imp. When you are done, you should get

ghci> run w_test
Output Store:
fromList [("X",IntVal 0),("Y",IntVal 10)]

ghci> run w_fact
Output Store:
fromList [("F",IntVal 2),("N",IntVal 0),("X",IntVal 1),("Z",IntVal 2)]

Problem 4: A Parser for WHILE

It is rather tedious to have to specify individual programs as Haskell values. For this problem, you will use parser combinators to build a parser for the WHILE language from the previous problem.

Parsing Constants

First, we will write parsers for the Value type

> valueP :: Parser Value
> valueP = intP <|> boolP

To do so, fill in the implementations of

> intP :: Parser Value
> intP = error "TBD" 

Next, define a parser that will accept a particular string s as a given value x

> constP :: String -> a -> Parser a
> constP s x = error "TBD"

and use the above to define a parser for boolean values where "true" and "false" should be parsed appropriately.

> boolP :: Parser Value
> boolP = error "TBD"

Continue to use the above to parse the binary operators

> opP :: Parser Bop 
> opP = error "TBD"

Parsing Expressions

Next, the following is a parser for variables, where each variable is one-or-more uppercase letters.

> varP :: Parser Variable
> varP = many1 upper

Use the above to write a parser for Expression values

> exprP :: Parser Expression
> exprP = error "TBD"

Parsing Statements

Next, use the expression parsers to build a statement parser

> statementP :: Parser Statement
> statementP = error "TBD" 

When you are done, we can put the parser and evaluator together in the end-to-end interpreter function

> runFile s = do p <- parseFromFile statementP s
>                case p of
>                  Left err   -> print err
>                  Right stmt -> run stmt

When you are done you should see the following at the ghci prompt

ghci> runFile "tests/test.imp"
Output Store:
fromList [("X",IntVal 0),("Y",IntVal 10)]

ghci> runFile "tests/fact.imp" 
Output Store:
fromList [("F",IntVal 2),("N",IntVal 0),("X",IntVal 1),("Z",IntVal 2)]