Homework 2
Haskell training, part II; semantics
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.
In this homework, we’re going to use Haskell more earnestly. We’ll start using some of its standard library’s functions and datatypes—we’ll even try defining our own datatypes.
Unless I say otherwise, you’re free to use any functions from the Prelude.
module Hw02 where
The following imports are needed for problem 5.
import qualified Data.Map as Map
import Data.Map (Map, (!))
import qualified Data.Set as Set
import Data.Set (Set)
Problem 1: recursion, naturally
We’re going to define each of the functions we defined in problem 1 of homework 1. But we’re going to do it using higher-order functions that are built into the Prelude. In particular, we’re going to use map
, filter
, and the two folds, foldr
and foldl
.
Define a function sumUp
that sums up a list of numbers.
sumUp :: [Int] -> Int
sumUp l = undefined
Define a function evens
that selects out the even numbers from a list.
evens :: [Int] -> [Int]
evens l = undefined
Define a function incAll
that increments a list of numbers by one.
incAll :: [Int] -> [Int]
incAll l = undefined
Define a function incBy
that takes a number and then increments a list of numbers by that number.
incBy :: Int -> [Int] -> [Int]
incBy n l = undefined
Define a function rev
that reverses a list. Don’t use anything but a folding function (your choice) and the list constructors.
rev :: [Int] -> [Int]
rev l = undefined
Define two versions of the function append
that appends two lists. One, appendr
, should use foldr
; the other, appendl
, should use foldl
. You can use the list constructors and rev
.
appendr :: [Int] -> [Int] -> [Int]
appendr l1 l2 = undefined
appendl :: [Int] -> [Int] -> [Int]
appendl l1 l2 = undefined
Problem 2: defining higher-order functions
We’re going to define several versions of the map
and filter
functions manually, using only natural recursion and folds—no using the Prelude or list comprehensions Note that I’ve written the polymorphic types for you.
Define map1
using natural recursion.
map1 :: (a -> b) -> [a] -> [b]
map1 = undefined
Define map2
using a folding function.
map2 :: (a -> b) -> [a] -> [b]
map2 f l = undefined
Define filter1
using natural recursion.
filter1 :: (a -> Bool) -> [a] -> [a]
filter1 = undefined
Define filter2
using a folding function.
filter2 :: (a -> Bool) -> [a] -> [a]
filter2 p l = undefined
Problem 3: more on datatypes
We’ve already briefly seen the Maybe
type in the first homework. In the next two problems, we’ll look at Maybe
, pairs, and Either
in more detail.
Haskell’s type system is rigid compared to most other languages. In time, you will come to view this as a feature—languages that let you ‘cheat’ their safety mechanisms end up making you pay for it with complexity elsewhere. But for now, let’s get familiar with the structures and strictures of types.
The Maybe
datatype introduces nullability in a controlled fashion—values of the type Maybe a
can be Nothing
or Just x
, where x
is a value of type a
.
Write a function mapMaybe
that behaves like map
when its higher-order function argument returns Just x
, but filters out results where the function returns Nothing
.
mapMaybe :: (a -> Maybe b) -> [a] -> [b]
mapMaybe = undefined
The pair datatype allows us to aggregate values: values of type (a,b)
will have the form (x,y)
, where x
has type a
and y
has type b
.
Write a function swap
that takes a pair of type (a,b)
and returns a pair of type (b,a)
.
swap :: (a,b) -> (b,a)
swap = undefined
Write a function pairUp
that takes two lists and returns a list of paired elements. If the lists have different lengths, return a list of the shorter length. (This is called zip
in the prelude. Don’t define this function using zip
!)
pairUp :: [a] -> [b] -> [(a,b)]
pairUp = undefined
Write a function splitUp
that takes a list of pairs and returns a pair of lists. (This is called unzip
in the prelude. Don’t define this function using unzip
!)
splitUp :: [(a,b)] -> ([a],[b])
splitUp = undefined
Write a function sumAndLength
that simultaneously sums a list and computes its length. You can define it using natural recursion or as a fold, but—traverse the list only once!
sumAndLength :: [Int] -> (Int,Int)
sumAndLength l = undefined
Problem 4: defining datatypes
The Either
datatype introduces choice in a controlled fashion—values of the type Either a b
can be either Left x
(where x
is an a
) or Right y
(where y
is a b
).
Define a datatype EitherList
that embeds the Either
type into a list. (This isn’t a good idea, but it’s a good exercise!)
To see what I mean, let’s combine lists and the Maybe
datatype. Here’s Haskell’s list datatype:
data [a] = [] | a:[a]
Here’s its Maybe datatype:
data Maybe a = Nothing | Just a
What kinds of values inhabit the type [Maybe a]
? There are two cases:
[]
, the empty lista:as
, wherea
has typeMaybe a
andas
is a list of type[Maybe a]
But we can really split it into three cases:
[]
, the empty lista:as
, whereas
is a list of type[Maybe a]
, and:a
isNothing
a
isJust a'
, wherea'
has typea
Put another way:
[]
, the empty listNothing:as
, whereas
is a list of type[Maybe a]
Just a:as
, wherea
has typea
andas
has type[Maybe a]
To define MaybeList, we’ll write a data structure that has those constructors expliclty.
data MaybeList a =
Nil
| ConsNothing (MaybeList a)
| ConsJust a (MaybeList a)
Note that these match up exactly with the last itemized list of cases.
Okay: do it for Either
! Fill in the functions below—they should behave like the Prelude functions. You’ll also have to fill in the type. We’ve given you the constructors’ names. Make sure your Cons
constructors takes arguments in the correct order, or we won’t be able to give you credit for any of this problem.
data EitherList a b =
Nil
| ConsLeft {- fill in -}
| ConsRight {- fill in -}
deriving (Eq, Show)
toEither :: [Either a b] -> EitherList a b
toEither = undefined
fromEither :: EitherList a b -> [Either a b]
fromEither = undefined
mapLeft :: (a -> c) -> EitherList a b -> EitherList c b
mapLeft = undefined
mapRight :: (b -> c) -> EitherList a b -> EitherList a c
mapRight = undefined
foldrEither :: (a -> c -> c) -> (b -> c -> c) -> c -> EitherList a b -> c
foldrEither = undefined
foldlEither :: (c -> a -> c) -> (c -> b -> c) -> c -> EitherList a b -> c
foldlEither = undefined
Problem 5: maps and sets
Haskell has many convenient data structures in its standard library. We’ll be playing with sets and maps today. Data.Map and Data.set are well documented on-line.
In this problem, we’ll use maps and sets to reason about graphs (in the network/graph theory sense, not in the statistical plotting sense).
We can start by defining what we mean by the nodes of the graph. We can use Haskell’s type system to keep from getting confused while letting nodes ‘just’ be strings.
newtype Node = Node { nodeName :: String } deriving (Eq,Ord,Show)
To create a Node
, we can use the constructor, like so:
a = Node "a"
b = Node "b"
c = Node "c"
d = Node "d"
e = Node "e"
The deriving
clause means we have ==
and `<=
and show :: Node -> String
for free, along with the function nodeName :: Node -> String
, which gets the name out of a Node
.
We can define a graph now as a map from Node
s to sets of Node
s. The Map
type takes two arguments: the type of the map’s key and the type of the map’s value. Here the keys will be Node
s and the values will be sets of nodes. The Set
type takes just one argument, like lists: the type of the set’s elements.
type Graph = Map Node (Set Node)
We don’t need to use newtype
here, because we’re less worried about confusing graphs with other kinds of maps.
Let’s start by building a simple graph, g1
:
- b -
/ \
a - - d
\ /
- c -
g1 = Map.fromList [(a, Set.fromList [b,c]),
(b, Set.fromList [a,d]),
(c, Set.fromList [a,d]),
(d, Set.fromList [b,c])]
Note that we’ve been careful to make sure the links are bidirectional: if the b
is in the value mapped by a
, then a
is in the value mapped by b
.
We can see what a
has edges to by looking it up in g1
:
aEdges = g1 ! a
Write a function isBidi
that checks whether a mapping is bidirectional. Feel free to use any function in Data.Map
, Data.Set
, or the Prelude, and write as many helper functions as you need.
isBidi :: Graph -> Bool
isBidi = undefined
Write a function bidify
that takes an arbitrary graph and makes it bidirectional.
bidify :: Graph -> Graph
bidify = undefined
Problem 6: arithmetic expressions
Our first language will be a simple one: arithmetic expressions using +, *, and negation.
data ArithExp =
Num Int
| Plus ArithExp ArithExp
| Times ArithExp ArithExp
| Neg ArithExp
deriving (Eq,Show)
(a) 10 points
We’re going to write an interpreter, which takes an arithmetic expression and evaluates it to a number. The general strategy here is the same as when we wrote naturally recursive functions over lists: break down each case of the datatype definition and use recursion on subparts.
For example, eval (Plus (Num 42) (Neg (Num 42)))
should yield 0
.
eval :: ArithExp -> Int
eval = undefined
(b) 10 points
Let’s extend our language to support subtraction—now we’re really cooking!
data ArithExp' =
Num' Int
| Plus' ArithExp' ArithExp'
| Sub' ArithExp' ArithExp'
| Times' ArithExp' ArithExp'
| Neg' ArithExp'
deriving (Eq,Show)
But wait: we should be able to encode subtraction using what we have, giving us a very nice evaluation function.
eval' :: ArithExp' -> Int
eval' = eval . translate
Write a function that will translate this extended language to our original language—make sure that eval'
does the right thing.
translate :: ArithExp' -> ArithExp
translate = undefined
(c) 10 points
In class, we gave denotational and rewrite semantics for the original ArithExp
language.
What do we need to add for a denotational semantics of ArithExp'
? What about a rewrite system?
fill in here