Data Types and Typeclasses
1 Natural numbers recommended atHome
Consider the set of natural numbers \(\mathbb{N}\), and observe that:
- zero is a natural number, and
- any other natural number is the successor of some other natural number.
Define a data type
Nat
representing natural numbers using the above observation.data Nat = Zero | Succ Nat
Write functions
toInt :: Nat -> Int
andfromInt :: Int -> Nat
that allows you to convert betweenNat
andInt
.toInt Zero = 0 toInt (Succ n) = 1 + toInt n fromInt i = case i `compare` 0 of LT -> error "negative number!" EQ -> Zero GT -> Succ (fromInt $ i-1)
2 atHome
Give a direct definition of the <
operator on lists. This definition
should not use operators like <=
for lists.
When trying out this definition using ghci
, do not use the <
symbol, since it is already defined in the Prelude
.
(<) :: Ord a => [a] -> [a] -> Bool
< [] = False
[] < _ = True
[] :_) < [] = False
(_:xs) < (y:ys) = x < y && xs < ys (x
3 Complex numbers recommended atHome
Write a data type
Complex
to represent complex numbers. A complex number is defined as a pair of real numbers \(a\) and \(b\), and is written as \(a + b*i\).data Complex = C Float Float
Make
Complex
an instance ofShow
,Eq
, andNum
(write the instances explicitly rather than deriving them). For more information about operations on complex numbers, see Wikipedia.instance Num Complex where C a b) + (C x y) = C (a + x) (b + y) (C a b) - (C x y) = C (a - x) (b - y) (C a b) * (C x y) = C (a*x-b*y) (a*y+b*x) (negate (C a b) = C (negate a) (negate b) abs (C a b) = C (a*a+b*b) 0 fromInteger i = C (fromInteger i) 0
4 Bikes atHome
Define data types that model the following situation as precisely as possible:
A bikeshop sells three kinds of bikes: city bikes, road bikes and mountainbikes, in three different sizes. In most cases, bike sizes are standardized into (small, medium, and large), however it is also possible for bikes to have a custom (integral) size (the size of the frame in inches). The mountainbikes and road bikes have gears. They have a cassette with many cogs on the rear wheel, and some of them may have a second chainring in the front (doubling the number of available gears). City bikes do not have gears. However, unlike the other types of bikes they have fenders either in the front, the back, or on both wheels). Fenders themselves come in two types; they are either made from plastic or metal.
-- some variations are possible, but the following answer captures the -- situation fairly precisely: data StandardSize = Small | Medium | Large data BikeSize = Standardized StandardSize | CustomSize Int data FrontChainrings = SingleChainring | TwoChainRings data Gears = Gears FrontChainrings Int data Fender = PlasticFender | MetalFender data Bike = CityBike BikeSize (Maybe Fender) (Maybe Fender) | RoadBike BikeSize Gears | MTB BikeSize Gears data Bikeshop = Bikeshop [Bike]
Consider a function
getFenders
that returns the fenders of a bike, if it has any. What would be a good type for this function?getFenders :: Bike -> (Maybe Fender, Maybe Fender) -- or potentially one could even define a custom return type: data Fenders = Fenders { frontFender :: Maybe Fender backFender :: Maybe Fender , }
Write the function
getFenders
Write a function
byGears
that lists all bikes available in the bikeshop, ordered by number of gears.
5 Sets atHome
Define a type
Set a
whose values represent sets of elements of typea
, and define a functionsubset :: Eq a => Set a -> Set a -> Bool
which checks whether all the elements in the first set also belong to the second.Use the
subset
function above to define anEq
instance forSet a
.Why do we have to define
Set a
as its own data type, instead of an alias over[a]
?
6 Finite
atHome
Define a class Finite
. This class has only one method: the list of
all the elements of that type. The idea is that such list is finite,
hence the name. Define the following instances for Finite
:
Bool
.Char
.(a, b)
for finitea
andb
.Set a
, as defined in the previous exercise, whena
is finite.a -> b
whenevera
andb
are finite anda
supports equality. Use this to makea -> b
an instance ofEq
.
class Finite a where
elements :: [a]
instance Finite Bool where
= [False, True]
elements
instance (Finite a, Finite b) => Finite (a, b) where
= [(x, y) | x <- elements, y <- elements]
elements
-- Auxiliary definition for Finite (Set a)
-- Computes all subsets for the given elements,
-- that is, all combinations where each element
-- in the list may or may not appear
allSubsets :: [a] -> [Set a]
= [[]]
allSubsets [] :vs) = let ss = allSubsets vs
allSubsets (vin ss ++ [v:s | s <- ss]
instance Finite a => Finite (Set a) where
= allSubsets elements
elements
-- Auxiliary definition for Finite (a -> b)
-- Computes all key-value pairs from two lists,
-- the first one gives the keys and the second
-- one gives the possible values
allKVPairs :: [k] -> [v] -> [[(k, v)]]
= [[]]
allKVPairs [] _ :ks) vs = [(k,v):kvs
allKVPairs (k| kvs <- allKVPairs ks vs
<- vs]
, v
instance (Finite a, Finite b, Eq a) => Finite (a -> b) where
= [\k -> fromJust (lookup k kv)
elements | kv <- allKVPairs elements elements]
7 Lines recommended atHome
Given the data types
data Point = Point Float Float -- Point x y is the point with coordinates (x, y) in the plane
data Vector = Vector Float Float -- Vector dx dy is the 2d vector in the direction (dx, dy)
data EqLine = EqLine Float Float Float -- EqLine a b c represents the line a * x + b * y + c = 0
data VectLine = VectLine Point Vector -- VectLine p v represents the line through p in the direction v
define a class Line
whose instances l
implement a method that calculates the distance from an l
to a Point
and a method vshift
that shifts the line vertically by a Float
offset.
class Line l where
distance :: l -> Point -> Float
vshift :: Float -> l -> l
Please make EqLine
and VectLine
instances of Line
.
instance Line EqLine where
EqLine a b c) (Point x y) = abs(a * x + b * y + c) / sqrt(a * a + b * b)
distance (EqLine a b c) = EqLine a b (c - b * f)
vshift f (
instance Line VectLine where
VectLine (Point x' y') (Vector dx dy)) (Point x y) = abs(dx * (y' - y) - (x' - x) * dy) / sqrt (dx ^ 2 + dy ^ 2)
distance (VectLine (Point x' y') v) = VectLine (Point x' (y' + f)) v vshift f (
Can you think of any more, different representations for lines? If so,
please implement them as a datatype and make them an instance of Line
.
-- For example:
data TwoPointLine = TwoPointLine Point Point -- TwoPointLine p1 p2 represents the line through p1 and p2
instance Line TwoPointLine where
TwoPointLine (Point x1 y1) (Point x2 y2)) (Point x y) = abs((x2 - x1) * (y1 - y) - (x1 - x) * (y2 - y1)) / sqrt ((x2 - x1) ^ 2 + (y2 - y1) ^ 2)
distance (TwoPointLine (Point x1 y1) (Point x2 y2)) = TwoPointLine (Point x1 (y1 + f)) (Point x2 (y2 + f)) vshift f (
-- Or:
data AngleLine = AngleLine Point Float -- AngleLine p theta represents the line through p with angle theta
instance Line AngleLine where
AngleLine (Point x' y') theta) (Point x y) = abs (cos theta * (y' - y) - sin theta * (x' - x))
distance (AngleLine (Point x' y') theta) = AngleLine (Point x' (y' + f)) theta vshift f (
-- Or this rather boring one:
distance :: l -> Point -> Float
vshift :: Float -> l -> l
data BoringLine = BoringLine {dist :: Point -> Float, vs :: Float -> BoringLine} -- BoringLine directly uses the required methods as a definition
instance Line BoringLine where
= dist
distance = flip vs vshift
Can you think of any more things we can compute for any line? Please add them as methods in the definition of Line
.
Can you give some of them default implementations?
-- For example:
class Line l where
distance :: l -> Point -> Float
vshift :: Float -> l -> l
isOn :: l -> Point -> Bool
= distance l p == 0
isOn l p -- come up with more methods yourself
8 atHome challenging
We can use a type class
class DGraph g where
succs :: Eq a => g a -> a -> [a]
for representing directed graphs.
The idea is that a
is a type of vertices, that g a
is the type of directed graphs with vertices of type a
and succs someGraph aVertex
gives the list of all successors of aVertex :: a
in the graph someGraph :: g a
.
We can define types
newtype PList k v = PList {keyValues :: [(k, v)]}
newtype SMPList k = SMPList (PList k [k])
data RoseTree l = RoseTree l [RoseTree l]
newtype FRoseTree l = FRoseTree [RoseTree l]
SMPList
and FRoseTree
give two different representations of directed graphs.
For example, the graph
can be represented as
= SMPList $ PList [(1, [2, 3]), (2, []), (3, [2, 4]), (4, [3])]
dgraph1SMPL = FRoseTree [one] where
dgraph1FRT = RoseTree 1 [two, tree]
one = RoseTree 2 []
two = RoseTree 3 [two, four]
three = RoseTree 4 [three] four
To warm up, please implement the graph
in both representations.
= SMPList $ PList [('a', ['b', 'd', 'c', 'e']), ('b', ['d']), ('d', ['e']), ('c', ['d', 'e']), ('e', [])] dgraph2SMPL
= FRoseTree [a] where
dgraph2FRT = RoseTree 'a' [b, d, c, e]
a = RoseTree 'b' [d]
b = RoseTree 'd' [e]
d = RoseTree 'c' [d, e]
c = RoseTree 'e' [] e
Please make SMPList
and FRoseTree
instances of DGraph
.
lookup' :: Eq k => k -> PList k v -> Maybe v
PList []) = Nothing
lookup' k (PList ((k', v) : kvs)) | k == k' = Just v
lookup' k (| otherwise = lookup' k (PList kvs)
handleMaybeList :: Maybe [l] -> [l]
Nothing = []
handleMaybeList Just ls) = ls
handleMaybeList (
instance DGraph SMPList where
SMPList m) l = handleMaybeList (lookup' l m) succs (
instance DGraph FRoseTree where
FRoseTree xs) y = concatMap (`succs'` y) xs where
succs (RoseTree x xs) y | x == y = map getVal xs
succs' (| otherwise = foldr (\x acc -> if null acc then succs' x y else acc) [] xs
RoseTree x _) = x getVal (
Can you come up with any more different representations of directed graphs? Please implement them as
parameterised datatypes and make them an instance of DGraph
. To practice some more, you can implement
your favourite directed graph (for example one of the two above) in your new representations.
-- For example:
newtype SPList l = SPList (PList l l) -- lists of pairs of vertices that are connected via an edge
instance DGraph SPList where
SPList g) a = [b | (a', b) <- keyValues g, a'== a ] succs (
-- Or this rather boring one:
newtype NDFun l = NDFun {getSuccs :: l -> [l]} -- directly using the successor function as a definition
instance DGraph NDFun where
= getSuccs succs
We want to write a function maxPaths
that takes a directed graph someGraph
– it should accept any representation –
and a list inits
of vertices as inputs and produces a list of all maximal directed paths, i.e. directed paths that cannot be made longer, in someGraph
that start from a vertex i
in inits
.
Please specify the type signature of maxPaths
.
maxPaths :: (Eq l, DGraph g) => g l -> [l] -> [[l]]
Now, please implement maxPaths
. You may assume, for simplicity, that it is only ever used on directed graphs without cycles.
= [[]]
maxPaths _ [] = concat [map (i:) (maxPaths someGraph (succs someGraph i)) | i <- inits] -- concatMap (\i -> map (i:) (maxPaths someGraph (succs someGraph i))) inits maxPaths someGraph inits
Can you come up with any more operations that we can perform on any directed graph?
-- For example a function depthFrom that calculates length of the longest path starting from a vertex in a graph
-- or a function descendants that computes a (lazy) list of all descendants (transitive closure of successors), infinite in case of cycles
Please add them to the type class and give their implementations. Can you use a default implementation?
-- For example
class DGraph g where
succs :: Eq a => g a -> a -> [a]
depthFrom :: Eq a => g a -> a -> Int -- length of the longest path starting from a vertex in a graph
= case succs someGraph x of
depthFrom someGraph x -> 0
[] -> 1 + maximum (map (depthFrom someGraph) xs)
xs descendants :: Eq a => g a -> a -> [a] -- (lazy) list of all descendants (transitive closure of successors), infinite in case of cycles
= c ++ concatMap (descendants someGraph) c where
descendants someGraph x = succs someGraph x c