Skip to content

Commit 10609ca

Browse files
committed
Set 10a Ex 4: new exercise
1 parent 5bd7d33 commit 10609ca

File tree

3 files changed

+65
-21
lines changed

3 files changed

+65
-21
lines changed

Diff for: exercises/Mooc/Test.hs

+2
Original file line numberDiff line numberDiff line change
@@ -40,6 +40,8 @@ expected =~? actual = actual ?~= expected
4040
infix 4 =~?
4141
infix 4 ?~=
4242

43+
approximateListEq expected actual = expectation expected actual (length expected == length actual && and (zipWith (\e a -> abs (e-a) < 0.01) expected actual))
44+
4345
hasElements expected actual = counterexample' (" Expected elements (in any order): " ++ show expected
4446
++ "\n Was: " ++ show actual)
4547
(sort expected == sort actual)

Diff for: exercises/Set10a.hs

+24-6
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ interleave = todo
4444
--
4545
-- Make sure your function works with infinite inputs as well!
4646
--
47-
-- Example:
47+
-- Examples:
4848
-- deal ["Hercule","Ariadne"] ["Ace","Joker","Heart"]
4949
-- ==> [("Ace","Hercule"),("Joker","Ariadne"),("Heart","Hercule")]
5050
-- take 4 (deal ["a","b","c"] (map show [0..]))
@@ -58,7 +58,25 @@ deal :: [String] -> [String] -> [(String,String)]
5858
deal = todo
5959

6060
------------------------------------------------------------------------------
61-
-- Ex 4: Given two lists, xs and ys, and an element z, generate an
61+
-- Ex 4: Compute a running average. Go through a list of Doubles and
62+
-- output a list of averages: the average of the first number, the
63+
-- average of the first two numbers, the first three numbers, and so
64+
-- on.
65+
--
66+
-- Make sure your function works with infinite inputs as well!
67+
--
68+
-- Examples:
69+
-- averages [] ==> []
70+
-- averages [3,2,1] ==> [3.0,2.5,2.0]
71+
-- take 10 (averages [1..]) ==> [1.0,1.5,2.0,2.5,3.0,3.5,4.0,4.5,5.0,5.5]
72+
73+
74+
75+
averages :: [Double] -> [Double]
76+
averages = todo
77+
78+
------------------------------------------------------------------------------
79+
-- Ex 5: Given two lists, xs and ys, and an element z, generate an
6280
-- infinite list that consists of
6381
--
6482
-- * the elements of xs
@@ -76,7 +94,7 @@ alternate :: [a] -> [a] -> a -> [a]
7694
alternate xs ys z = todo
7795

7896
------------------------------------------------------------------------------
79-
-- Ex 5: Check if the length of a list is at least n. Make sure your
97+
-- Ex 6: Check if the length of a list is at least n. Make sure your
8098
-- function works for infinite inputs.
8199
--
82100
-- Examples:
@@ -88,7 +106,7 @@ lengthAtLeast :: Int -> [a] -> Bool
88106
lengthAtLeast = todo
89107

90108
------------------------------------------------------------------------------
91-
-- Ex 6: The function chunks should take in a list, and a number n,
109+
-- Ex 7: The function chunks should take in a list, and a number n,
92110
-- and return all sublists of length n of the original list.
93111
--
94112
-- Make sure your function works with infinite inputs. The function
@@ -102,7 +120,7 @@ chunks :: Int -> [a] -> [[a]]
102120
chunks = todo
103121

104122
------------------------------------------------------------------------------
105-
-- Ex 7: Define a newtype called IgnoreCase, that wraps a value of
123+
-- Ex 8: Define a newtype called IgnoreCase, that wraps a value of
106124
-- type String. Define an `Eq` instance for IgnoreCase so that it
107125
-- compares strings in a case-insensitive way.
108126
--
@@ -117,7 +135,7 @@ chunks = todo
117135

118136

119137
------------------------------------------------------------------------------
120-
-- Ex 8: Here's the Room type and some helper functions from the
138+
-- Ex 9: Here's the Room type and some helper functions from the
121139
-- course material. Define a cyclic Room structure like this:
122140
--
123141
-- * maze1 has the description "Maze"

Diff for: exercises/Set10aTest.hs

+39-15
Original file line numberDiff line numberDiff line change
@@ -20,11 +20,12 @@ main = score tests
2020
tests = [(1,"doublify",[ex1_finite, ex1_infinite])
2121
,(2,"interleave",[ex2_finite, ex2_infinite_1, ex2_infinite_2])
2222
,(3,"deal",[ex3_examples, ex3_finite, ex3_infinite_1, ex3_infinite_2])
23-
,(4,"alternate",[ex4_examples, ex4])
24-
,(5,"lenghtAtLeast",[ex5_finite, ex5_infinite])
25-
,(6,"chunks",[ex6_finite, ex6_infinite])
26-
,(7,"IgnoreCase",[ex7_type, ex7_works])
27-
,(8,"maze",[ex8_1, ex8_2])]
23+
,(4,"averages",[ex4_simple, ex4_finite, ex4_infinite])
24+
,(5,"alternate",[ex5_examples, ex5])
25+
,(6,"lenghtAtLeast",[ex6_finite, ex6_infinite])
26+
,(7,"chunks",[ex7_finite, ex7_infinite])
27+
,(8,"IgnoreCase",[ex8_type, ex8_works])
28+
,(9,"maze",[ex9_1, ex9_2])]
2829

2930
-- -- -- --
3031

@@ -88,46 +89,69 @@ ex3_infinite_1 = forAllShrink_ (listOf1 word) $ \names ->
8889
ex3_infinite_2 =
8990
$(testing' [|take 10 (deal (repeat "me") (repeat "card"))|]) (?==replicate 10 ("card","me"))
9091

91-
ex4_examples = conjoin [$(testing' [|take 20 (alternate "abc" "def" ',')|]) (?=="abc,def,abc,def,abc,")
92+
93+
94+
ex4_simple = conjoin [$(testing [|averages [1.0,2.0,3.0]|]) (approximateListEq [1.0,(1+2)/2,(1+2+3)/3])
95+
,$(testing [|averages [7,2,5,8]|]) (approximateListEq [7,(7+2)/2,(7+2+5)/3,(7+2+5+8)/4])
96+
,let e = [] :: [Double] in $(testing [|averages e|]) (?==e)]
97+
98+
ex4_finite = forAllBlind (elements [0,1,2,3]) $ \base ->
99+
forAllBlind (elements [1,2,3,4,5,6]) $ \step ->
100+
forAllBlind (choose (2,7)) $ \len ->
101+
let input = [base + i*step | i <- [0..len]]
102+
output = [(j*base + (j-1)*j*step/2)/j | j <- [1..len+1]]
103+
in $(testing [|averages input|]) (approximateListEq output)
104+
105+
ex4_infinite = forAllBlind (elements [0,1,2,3,4,5,6,7,8,9]) $ \a ->
106+
forAllBlind (elements [0,1,2,3,4,5,6,7,8,9]) $ \b ->
107+
forAllBlind (choose (0,1000)) $ \i ->
108+
counterexample ("With a=" ++ show a ++ ", b=" ++ show b) $
109+
$(testing' [|averages (cycle [a,b])|]) $ \res ->
110+
counterexample (" element at index " ++ show i) $
111+
let na = fromIntegral (div i 2 + 1)
112+
nb = fromIntegral (div (i+1) 2)
113+
in res !! i ?~= (na*a + nb*b)/(na+nb)
114+
115+
ex5_examples = conjoin [$(testing' [|take 20 (alternate "abc" "def" ',')|]) (?=="abc,def,abc,def,abc,")
92116
,$(testing' [|take 10 (alternate [1,2] [3,4,5] 0)|]) (?==[1,2,0,3,4,5,0,1,2,0])]
93117

94-
ex4 = forAllBlind (choose (1,3)) $ \n ->
118+
ex5 = forAllBlind (choose (1,3)) $ \n ->
95119
forAllBlind (choose (1,6)) $ \m ->
96120
forAll_ $ \(NonNegative i) ->
97121
$(testing [|alternate (replicate n 1) (replicate m 1) 0|]) $ \was ->
98122
counterexample (" Index "++show i) $
99123
(was !! i ?== if mod i (2+n+m) `elem` [n,n+1+m] then 0 else 1)
100124

101-
ex5_finite = forAll_ $ \(is::[Int]) ->
125+
ex6_finite = forAll_ $ \(is::[Int]) ->
102126
forAll_ $ \(NonNegative n) ->
103127
$(testing [|lengthAtLeast n is|]) (?==(length is >= n))
104128

105-
ex5_infinite = forAll_ $ \(Positive (i::Int)) ->
129+
ex6_infinite = forAll_ $ \(Positive (i::Int)) ->
106130
forAll_ $ \(NonNegative n) ->
107131
counterexample ("With n = " ++ show n ++ ", i = " ++ show i) $
108132
$(testing' [|lengthAtLeast n (repeat i)|]) (?==True)
109133

110-
ex6_finite = forAllBlind (choose (1,6)) $ \n ->
134+
ex7_finite = forAllBlind (choose (1,6)) $ \n ->
111135
forAllShrink_ (listOf word) $ \ws ->
112136
$(testing [|chunks n ws|]) (?==[[ws!!i | i <- [j..j+n-1]] | j <- [0..length ws - n]])
113137

114-
ex6_infinite = forAllBlind (choose (1,10)) $ \n ->
138+
ex7_infinite = forAllBlind (choose (1,10)) $ \n ->
115139
forAllBlind (choose (1,25)) $ \k ->
116140
counterexample ("With k = "++show k++", n = "++show n) $
117141
$(testing' [|take k (chunks n [0..])|]) (?==[[j..j+n-1] | j <- [0..k-1]])
118142

119143
shuffleCase w = (do s <- vectorOf (length w) (elements [toLower,toUpper])
120144
return (zipWith ($) s w)) `suchThat` (/=w)
121145

122-
ex7_type = $(do let s = "IgnoreCase"
146+
ex8_type = $(do let s = "IgnoreCase"
123147
n <- lookupTypeName s
124148
case n of
125149
Nothing -> [|counterexample ("Type "++s++" not defined!") False|]
126150
Just n -> do info <- reify n
127151
case info of TyConI (NewtypeD _ _ _ _ _ _) -> [|property True|]
128152
_ -> [|counterexample ("Definition "++s++" is not a newype declaration!") False|])
129153

130-
ex7_works =
154+
ex8_works =
131155
$(hasType' "ignorecase" "String -> IgnoreCase") $ \ignorecase ->
132156
$(withInstance "Eq" "IgnoreCase" [|(==)|]) $ \((==)) ->
133157
property $ do
@@ -156,12 +180,12 @@ play room [] = [describe room]
156180
play room (d:ds) = case move room d of Nothing -> [describe room]
157181
Just r -> describe room : play r ds
158182

159-
ex8_1 = forAllShrink_ (choose (0,20)) $ \i ->
183+
ex9_1 = forAllShrink_ (choose (0,20)) $ \i ->
160184
counterexample ("with i = " ++ show i) $
161185
conjoin [$(testing' [|play maze (replicate i "Left")|]) (?==take (i+1) (cycle ["Maze","Deeper in the maze","Elsewhere in the maze"]))
162186
,$(testing' [|play maze (replicate i "Right")|]) (?==take (i+1) (cycle ["Maze","Elsewhere in the maze","Deeper in the maze"]))]
163187

164-
ex8_2 = forAllShrinkBlind (listOf (elements ["Left","Right"])) subterms $ \dirs ->
188+
ex9_2 = forAllShrinkBlind (listOf (elements ["Left","Right"])) subterms $ \dirs ->
165189
let cnt = sum (map (\d -> case d of "Left" -> 1; "Right" -> -1) dirs)
166190
answer = ["Maze","Deeper in the maze","Elsewhere in the maze"] !! mod cnt 3
167191
in counterexample ("with dirs = " ++ show dirs) $

0 commit comments

Comments
 (0)