Skip to content

Commit 00dfc7b

Browse files
committed
1 parent d3bf0bc commit 00dfc7b

32 files changed

+1532
-0
lines changed

exercises/BinTree/BinTree.hs

Lines changed: 106 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,106 @@
1+
module BinTree where
2+
3+
{-
4+
We're going to define functions that operate on a tree in order to use it
5+
as a binary search tree, i.e. a tree where nodes have a value, and where a
6+
node's left subtree consists of strictly smaller values that its own value,
7+
and vice-versa for its right subtree.
8+
First, let's define the data structure for a binary tree of Ints:
9+
-}
10+
11+
data BinTree = Nil -- ← An empty tree
12+
| Node Int BinTree BinTree -- ← A node with an Int value and two
13+
deriving (Eq, Show) -- children, that are also BinTrees
14+
15+
{-
16+
To use our binary tree as a binary *search* tree we have to create
17+
functions that make sure that the following invariants hold:
18+
19+
1. The left subtree of a node contains only nodes with values less than the
20+
node's value.
21+
2. The right subtree of a node contains only nodes with value greater than
22+
the node's value.
23+
3. There must be no duplicate nodes.
24+
25+
Let's look at how our data structure evolves when inserting the values 2,
26+
3, 1, 4 in that order:
27+
28+
* Step 0: Empty tree:
29+
30+
Nil → Nil
31+
32+
* Step 1: inserting 2 gives us:
33+
34+
Node 2 Nil Nil → 2
35+
/ \
36+
Nil Nil
37+
* Step 2: inserting 3 gives us:
38+
39+
Node 2 Nil (Node 3 Nil Nil) → 2
40+
/ \
41+
Nil 3
42+
/ \
43+
Nil Nil
44+
* Step 3: inserting 1 gives us:
45+
46+
Node 2 (Node 1 Nil Nil) (Node 3 Nil Nil) → __2__
47+
/ \
48+
1 3
49+
/ \ / \
50+
Nil Nil Nil Nil
51+
* Step 4: inserting 4 gives us:
52+
53+
Node 2 (Node 1 Nil Nil) (Node 3 Nil (Node 4 Nil Nil)) → __2__
54+
/ \
55+
1 3
56+
/ \ / \
57+
Nil Nil Nil 4
58+
/ \
59+
Nil Nil
60+
61+
Ok. Let's build this insert function step by step. Its type will be the
62+
following:
63+
-}
64+
65+
insert :: Int -> BinTree -> BinTree
66+
67+
{- The first case is inserting into an empty tree: -}
68+
69+
insert n Nil = _YOUR_CODE_HERE
70+
71+
{- ... the next case is inserting into a non-empty tree (i.e. a `Node`). We
72+
need to find out whether to insert into the left or the right subtree. and
73+
then our problem has been reduced to inserting a value into an BinTree again.
74+
We (soon) have a function to do that, don't we..? :) -}
75+
76+
insert n _YOUR_CODE_HERE {- code for matching a non-empty tree -} = _YOUR_CODE_HERE
77+
78+
{-
79+
Next, we're goint to create a function that does an in-order traversal of a
80+
binary tree. An in-order travelsal means first traversing the left subtree
81+
(smaller values), then a node's own value, and last its right subtree (larger
82+
values). The result – if `insert` is correct – should be a sorted list.
83+
Remembmer, to concatenate two lists, you can use the function (++):
84+
85+
[1,2,3] ++ [4] ++ [5,6] = [1,2,3,4,5,6]
86+
-}
87+
88+
inorder :: BinTree -> [Int]
89+
inorder Nil = _YOUR_CODE_HERE -- What's the only value we can return here?
90+
inorder (Node value left right) = _YOUR_CODE_HERE
91+
92+
{-
93+
Bonus questions:
94+
95+
Our binary search tree is only for `Int`s – what would it take to
96+
generalize it for any type `a`? Can our data type and the functions really
97+
work for *any* type?
98+
99+
Change `BinTree`, `insert` and `inorder` so that they are no longer
100+
Int-specific.
101+
102+
Can you think of reasons why this naïve BinTree might not be that great in
103+
practice? :)
104+
-}
105+
106+
_YOUR_CODE_HERE = undefined -- ignore me

exercises/BinTree/BinTreeSpec.hs

Lines changed: 30 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,30 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
2+
3+
module BinTree.BinTreeSpec where
4+
5+
import BinTree (BinTree (..))
6+
import qualified BinTree
7+
8+
import Data.List (foldl', nub, sort)
9+
import qualified Test.QuickCheck as QC
10+
import Test.Hspec
11+
12+
spec = do
13+
describe "BinTree.insert" $
14+
it "insert 1 into an empty tree" $
15+
BinTree.insert (1 :: Int) Nil `shouldBe` Node 1 Nil Nil
16+
17+
describe "BinTree.insert" $
18+
it "insert 2 1 3 4 into an empty tree" $
19+
BinTree.insert (4 :: Int) (BinTree.insert 1 (BinTree.insert 3 (BinTree.insert 2 Nil)))
20+
`shouldBe` Node 2 (Node 1 Nil Nil) (Node 3 Nil (Node 4 Nil Nil))
21+
22+
describe "BinTree.insert" $
23+
it "make sure duplicates are ignored" $
24+
BinTree.insert (3 :: Int) (BinTree.insert 1 (BinTree.insert 3 (BinTree.insert 2 Nil)))
25+
`shouldBe` Node 2 (Node 1 Nil Nil) (Node 3 Nil Nil)
26+
27+
describe "BinTree.inorder" $
28+
it "make sure an in-order traversal ouputs a sorted list" $
29+
let propSorted (xs :: [Int]) = BinTree.inorder (foldl' (flip BinTree.insert) Nil xs) == (sort . nub) xs
30+
in QC.quickCheck propSorted

exercises/Functions/Functions.hs

Lines changed: 86 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,86 @@
1+
module Functions where
2+
3+
{-
4+
In this module we will learn how to define and apply functions.
5+
-}
6+
7+
8+
-- Defining a function taking one parameter:
9+
welcome name = "Welcome, " ++ name ++ "."
10+
-- ^ ^ `------------^------------'
11+
-- name parameter body
12+
13+
{-
14+
There's no keyword like "def", "function" or anything preceding the name, just:
15+
<functionName> <arguments> = <body>
16+
-}
17+
18+
-- Calling a function with arguments
19+
welcomeSirOrMadam = welcome "Sir or Madam"
20+
21+
{-
22+
Now if we do multiple function applications and intend on passing the result
23+
of the first application to the second application and so on, we would have to
24+
use parentheses to remove abiguities:
25+
-}
26+
printWelcomeMessage2 = putStrLn (welcome "Welcome to the present")
27+
{-
28+
otherwise the compiler would interpret that function this way:
29+
30+
printWelcomeMessage2 = (putStrLn welcome) "Welcome to the present"
31+
^ ^ ^
32+
function to apply arg arg to what (putstrln welcome) returned
33+
34+
So a general tip is: if in doubt, add parentheses!
35+
-}
36+
37+
38+
{-
39+
Exercise:
40+
Use the multiply function to return the product of 10 and 20.
41+
Fill in your answer as the body of multiply10by20.
42+
-}
43+
-- This function returns the product of its arguments
44+
multiply arg1 arg2 = arg1 * arg2
45+
46+
multiply10by20 = _YOUR_CODE_HERE
47+
48+
49+
{-
50+
Exercise:
51+
Define a function, plus, that takes two arguments and returns their sum
52+
-}
53+
plus :: Integer -> Integer -> Integer
54+
plus arg1 arg2 = _YOUR_CODE_HERE
55+
56+
57+
{-
58+
Exercise:
59+
Define a function, sum3, that takes 3 arguments and returns their sum.
60+
... and you must use the plus function to do so!
61+
-}
62+
sum3 :: Integer -> Integer -> Integer -> Integer
63+
sum3 arg1 arg2 arg3 = _YOUR_CODE_HERE
64+
65+
66+
{-
67+
Exercise:
68+
Define isDollar that takes a Char and returns
69+
True only if that character is a dollar sign ($).
70+
-}
71+
isDollar :: Char -> Bool
72+
isDollar character = _YOUR_CODE_HERE
73+
74+
75+
{-
76+
Exercise:
77+
Define an "exclusive or" function: http://en.wikipedia.org/wiki/Exclusive_or#Truth_table
78+
You probably want to use the following functions:
79+
80+
(&&) :: Bool -> Bool -> Bool
81+
(||) :: Bool -> Bool -> Bool
82+
-}
83+
xor :: Bool -> Bool -> Bool
84+
xor arg1 arg2 = _YOUR_CODE_HERE
85+
86+
_YOUR_CODE_HERE = undefined -- ignore me

exercises/Functions/FunctionsSpec.hs

Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
module Functions.FunctionsSpec where
2+
3+
import qualified Functions
4+
5+
import qualified Test.QuickCheck as QC
6+
import Test.Hspec
7+
8+
spec = do
9+
describe "Functions.multiply10by20" $
10+
it "returns 200" $
11+
Functions.multiply10by20 `shouldBe` 200
12+
13+
describe "Functions.plus" $
14+
it "adds to *arbitrary* numbers" $
15+
QC.property $ \x y -> Functions.plus x y == x + y
16+
17+
describe "Functions.sum3" $
18+
it "adds three *arbitrary* numbers" $
19+
QC.property $ \x y z -> Functions.sum3 x y z == x + y + z
20+
21+
describe "Functions.isDollar" $ do
22+
it "returns true for '$'" $
23+
Functions.isDollar '$' `shouldBe` True
24+
it "returns false for anything but '$'" $
25+
any Functions.isDollar ['%'..'z'] `shouldBe` False
26+
27+
describe "Functions.xor" $
28+
it "is correct" $
29+
QC.property $ \x y -> Functions.xor x y == (x && not y) || (y && not x)
Lines changed: 75 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,75 @@
1+
module HigherOrderFunctions where
2+
3+
{-
4+
Now for some potentially mind blowing business: we're going to implement
5+
sets of integers, as functions!
6+
The idea is that a set is a boolean function for all integers, and
7+
returns true if a given integer is part of the set and false otherwise.
8+
-}
9+
10+
-- We create a type alias to avoid repetition of (Int -> Bool)
11+
type Set = (Int -> Bool)
12+
13+
{-
14+
Sets are then defined as functions that returns true/false based on the
15+
number they're given.
16+
-}
17+
18+
-- The set of even numbers
19+
evens :: Set
20+
evens n = n `mod` 2 == 0
21+
22+
-- The set of positive numbers
23+
positives :: Set
24+
positives n = n > 0
25+
26+
-- The set of numbers divisible by 3
27+
divBy3 :: Set
28+
divBy3 n = n `mod` 3 == 0
29+
30+
-- The empty set
31+
emptySet :: Set
32+
emptySet _ = False
33+
34+
{-
35+
The lightness of sets as functions makes it very cheap to
36+
combine them with set operators, such as intersect and union.
37+
-}
38+
39+
-- The intersection of two sets is a function that returns a function that
40+
-- takes `x` and checks if it's a member of both sets.
41+
intersect :: Set -> Set -> Set
42+
intersect a b = \x -> let memberOfA = a x
43+
memberOfB = b x
44+
in memberOfA && memberOfB
45+
46+
-- Combinations
47+
mySet1 = intersect evens divBy3
48+
49+
{-
50+
Exercise:
51+
Write a function that returns a set containing only the provided argument.
52+
-}
53+
54+
singleton :: Int -> Set
55+
singleton n = _YOUR_CODE_HERE
56+
57+
{-
58+
Exercise:
59+
Write a function for set union.
60+
-}
61+
62+
union :: Set -> Set -> Set
63+
union a b = _YOUR_CODE_HERE
64+
65+
{-
66+
Exercise:
67+
Write a function for set difference. Given two sets a and b, the result
68+
should be a set with only those numbers that appear in set a, but not is
69+
set b.
70+
-}
71+
72+
difference :: Set -> Set -> Set
73+
difference a b = _YOUR_CODE_HERE
74+
75+
_YOUR_CODE_HERE = undefined -- ignore me
Lines changed: 22 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,22 @@
1+
module HigherOrderFunctions.HigherOrderFunctionsSpec where
2+
3+
import qualified HigherOrderFunctions as HOF
4+
5+
import qualified Test.QuickCheck as QC
6+
import Test.Hspec
7+
8+
spec = do
9+
describe "HigherOrderFunctions.singleton" $ do
10+
it "should contain only the given number" $ do
11+
map (HOF.singleton 3) [1,2,3,4] `shouldBe` [False, False, True, False]
12+
13+
describe "HigherOrderFunctions.union" $ do
14+
let twoOrThree = HOF.singleton 3 `HOF.union` HOF.singleton 2
15+
expected = 2
16+
in it "should be the union of two sets" $ do
17+
map twoOrThree [1,2,3,4] `shouldBe` [False, True, True, False]
18+
19+
describe "HigherOrderFunctions.difference" $ do
20+
let evensExceptTwo = HOF.evens `HOF.difference` HOF.singleton 2
21+
in it "should be the difference of two sets" $ do
22+
map evensExceptTwo [1,2,3,4] `shouldBe` [False, False, False, True]

0 commit comments

Comments
 (0)