Homework 8
Type classes
This homework is written in literate Haskell; you can download the raw source to fill in yourself. You’re welcome to submit literate Haskell yourself, or to start fresh in a new file, literate or not.
Please submit homeworks via the DCI submission page.
module Hw08 where
import Control.Applicative
import Data.Char
This homework will be published in two parts. Both parts are due on 2015-11-15, but the second part won’t be published until 2015-11-09.
The first part consists of three problems, all on type classes.
Second part consists of two problems: one using the material from lecture on Wednesday, one a short answer question.
Part 1
Problem 1: Eq
and Show
(5pts)
data ArithExp =
Num Int
| Plus ArithExp ArithExp
| Times ArithExp ArithExp
| Neg ArithExp
Write Eq
and Show
instances for ArithExp
.
The Eq
instance should compare for structural equality—Plus (Num 5) (Num 3) == Plus (Num 5) (Num 3)
yield True
, but Plus (Num 5) (Num 3) == Plus (Num 3) (Num 5)
yields False
.
The Show
instance should print as few parentheses as possible. That is, show (Plus (Num 5) (Plus (Num 6) (Num 36)))
should return "5 + 6 + 36"
, not "5 + (6 + 36)"
. Similarly, show (Plus (Num 5) (Times (Num 6) (Num 36)))
should return 5 + 6 * 36
, because multiplication has a higher precedence than addition. But show (Times (Num 5) (Plus (Num 6) (Num 36)))
should return "5 * (6 + 36)"
“.
instance Eq ArithExp where
_ == _ = undefined
instance Show ArithExp where
show = undefined
Problem 2: Setlike
(10pts)
Here is a type class Setlike
. A given type constructor f
, of kind * -> *
, is Setlike
if we can implement the following methods for it. (Recall Listlike
from lecture.)
class Setlike f where
emp :: f a
singleton :: a -> f a
union :: Ord a => f a -> f a -> f a
union = fold insert
insert :: Ord a => a -> f a -> f a
insert = union . singleton
delete :: Ord a => a -> f a -> f a
delete x s = fold (\y s' -> if x == y then s' else insert y s') emp s
isEmpty :: f a -> Bool
isEmpty = (==0) . size
size :: f a -> Int
size = fold (\_ count -> count + 1) 0
isIn :: Ord a => a -> f a -> Bool
isIn x s = maybe False (const True) $ getElem x s
getElem :: Ord a => a -> f a -> Maybe a
fold :: (a -> b -> b) -> b -> f a -> b
toAscList :: f a -> [a] -- must return the list sorted ascending
toAscList = fold (:) []
In the rest of this problem, you’ll define some instances for Setlike
and write some code using the Setlike
interface. Please write the best code you can. Setlike
has some default definitions, but sometimes you can write a function that’s more efficient than the default. Do it. Write good code.
Define an instance of Setlike
for lists. Here’s an example that should work when you’re done—it should be the set {0,2,4,6,8}.
evensUpToTen :: [Int]
evensUpToTen = fold insert emp [0,2,4,6,8]
Here’s a type of binary trees. Define a Setlike
for BSTs, using binary search algorithms. Write good code. I expect insertion, lookup, and deletion to all be O(log n).
data BST a = Empty | Node (BST a) a (BST a)
Write Eq
and Show
instances for BSTs. These might be easier to write using the functions below.
instance Ord a => Eq (BST a) where
s1 == s2 = undefined
instance Show a => Show (BST a) where
show = undefined
Write the following set functions. You’ll have to use the Setlike
interface, since you won’t know which implementation you get.
fromList
should convert a list to a set.
fromList :: (Setlike f, Ord a) => [a] -> f a
fromList = undefined
difference
should compute the set difference: X - Y = { x in X | x not in Y }.
difference :: (Setlike f, Ord a) => f a -> f a -> f a
difference xs ys = undefined
subset
should determine whether the first set is a subset of the other one. X ⊆ Y iff ∀ x. x ∈ X implies x ∈ Y.
subset :: (Setlike f, Ord a) => f a -> f a -> Bool
subset xs ys = undefined
Problem 3: maps from sets (10pts)
Finally, let’s use sets to define maps—a classic data structure approach.
We’ll define a special notion of key-value pairs, KV k v
, with instances to force comparisons just on the key part.
newtype KV k v = KV { kv :: (k,v) }
instance Eq k => Eq (KV k v) where
(KV kv1) == (KV kv2) = fst kv1 == fst kv2
instance Ord k => Ord (KV k v) where
compare (KV kv1) (KV kv2) = compare (fst kv1) (fst kv2)
instance (Show k, Show v) => Show (KV k v) where
show (KV (k,v)) = show k ++ " |-> " ++ show v
type Map f k v = f (KV k v)
type ListMap k v = Map [] k v
type TreeMap k v = Map BST k v
Now define the following map functions that work with Setlike
.
emptyMap :: Setlike f => Map f k v
emptyMap = undefined
lookup :: (Setlike f, Ord k) => k -> Map f k v -> Maybe v
lookup k m = undefined
extend :: (Setlike f, Ord k) => k -> v -> Map f k v -> Map f k v
extend k v m = undefined
remove :: (Setlike f, Ord k) => k -> Map f k v -> Map f k v
remove k m = undefined
toAssocList :: Setlike f => Map f k v -> [(k,v)]
toAssocList = undefined
You’ll have to think hard about what to do for lookup
and remove
… what should v
be? Can you use lazy evaluation to your advantage?
Part 2
Problem 4: parsing with Applicative
(10pts)
Note that you’ll need to add import Control.Applicative
to the top of the file to get the below to work. You’ll also need to rename the empty
method of the Setlike
class to emp
. Sorry for the confusion. :(
We’ll use Applicative
to do some parsing. Here are the definitions from lecture.
pair :: Applicative f => f a -> f b -> f (a,b)
pair = liftA2 (,)
first :: (a -> b) -> (a,c) -> (b,c)
first f (a,c) = (f a, c)
newtype Parser a = Parser { parse :: String -> Maybe (a,String) }
instance Functor Parser where
fmap f p = Parser $ \s -> maybe Nothing (Just . first f) (parse p s)
instance Applicative Parser where
pure a = Parser $ \s -> Just (a,s)
f <*> a = Parser $ \s -> maybe Nothing (\(g,s') -> parse (fmap g a) s') $ parse f s
instance Alternative Parser where
empty = Parser $ const empty
l <|> r = Parser $ \s -> parse l s <|> parse r s
ensure :: (a -> Bool) -> Parser a -> Parser a
ensure p parser = Parser $ \s ->
case parse parser s of
Nothing -> Nothing
Just (a,s') -> if p a then Just (a,s') else Nothing
lookahead :: Parser (Maybe Char)
lookahead = Parser f
where f [] = Just (Nothing,[])
f (c:s) = Just (Just c,c:s)
eof :: Parser ()
eof = Parser $ \s -> if null s then Just ((),[]) else Nothing
zeroOrMore, oneOrMore :: Parser a -> Parser [a]
oneOrMore p = (:) <$> p <*> zeroOrMore p -- a/k/a some
zeroOrMore p = oneOrMore p <|> pure [] -- a/k/a many
satisfy :: (Char -> Bool) -> Parser Char
satisfy p = Parser f
where f [] = Nothing
f (x:xs) = if p x then Just (x,xs) else Nothing
spaces :: Parser ()
spaces = pure () <* zeroOrMore (satisfy isSpace)
char :: Char -> Parser Char
char c = spaces *> satisfy (==c)
str :: String -> Parser String
str s = spaces *> loop s
where loop [] = pure []
loop (c:cs) = (:) <$> satisfy (==c) <*> loop cs
type Id = String
data Expr =
EVar Id
| ETrue
| EFalse
| EIf Expr Expr Expr
| ENum Int
| EIncr Expr
| EDecr Expr
| EIsZero Expr
| EApp Expr Expr
| ELam Id Expr
deriving (Show, Eq)
Write a parser for the Expr language from HW05.
expr :: Parser Expr
expr = undefined
One of the key issues will be discriminating identifiers from tokens. You’ll want to use lookahead
to do that. Good luck!
Problem 5: your thoughts on parsing (5pts)
You’ve now seen three different styles of parser—manually, using a lexer/parser generator, and using combinators—and written two of them, at least.
What are the pros and cons of each style?
What do you prefer?
Are there times when you would use one kind of parser over another?