Skip to content

Commit d446c48

Browse files
committed
ch6 exercise solutions
1 parent a9a5be2 commit d446c48

File tree

2 files changed

+96
-11
lines changed

2 files changed

+96
-11
lines changed

exercises/chapter6/test/Main.purs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ import Data.Hashable (hash)
66
import Data.List (List(..), (:))
77
import Effect (Effect)
88
import Partial.Unsafe (unsafePartial)
9-
import Test.Solutions (Complex(..), Extended(..), Hour(..), Multiply(..), NonEmpty(..), OneMore(..), Self(..), act)
9+
import Test.Solutions (Complex(..), Extended(..), Hour(..), Multiply(..), NonEmpty(..), OneMore(..), Self(..), act, arrayHasDuplicates, unsafeMaximum)
1010
import Test.Unit (suite, test)
1111
import Test.Unit.Assert as Assert
1212
import Test.Unit.Main (runTest)
@@ -26,7 +26,6 @@ main =
2626
$ Assert.equal "1.0+2.0i"
2727
$ show
2828
$ Complex { real: 1.0, imaginary: 2.0 }
29-
{- Move this block comment starting point to enable more tests
3029
test "Show Negative Complex"
3130
$ Assert.equal "1.0-2.0i"
3231
$ show
@@ -187,4 +186,3 @@ main =
187186
$ Assert.equal (hash $ Hour 1)
188187
$ hash
189188
$ Hour 14
190-
-}
Lines changed: 95 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -1,27 +1,81 @@
11
module Test.Solutions where
22

33
import Prelude
4+
import Data.Array (length, nubByEq)
5+
import Data.Foldable (class Foldable, foldMap, foldl, foldr, maximum)
6+
import Data.Hashable (class Hashable, hash, hashEqual)
7+
import Data.Maybe (Maybe(..))
8+
import Data.Monoid (power)
49

510
newtype Complex
611
= Complex
712
{ real :: Number
813
, imaginary :: Number
914
}
1015

16+
instance showComplex :: Show Complex where
17+
show (Complex c) =
18+
let
19+
optional_plus
20+
| c.imaginary >= 0.0 = "+"
21+
| otherwise = ""
22+
in
23+
show c.real <> optional_plus <> show c.imaginary <> "i"
24+
25+
instance eqComplex :: Eq Complex where
26+
eq (Complex a) (Complex b) = a.real == b.real && a.imaginary == b.imaginary
27+
1128
data NonEmpty a
1229
= NonEmpty a (Array a)
1330

31+
instance eqNonEmpty :: Eq a => Eq (NonEmpty a) where
32+
eq (NonEmpty e1 a1) (NonEmpty e2 a2) = e1 == e2 && a1 == a2
33+
34+
instance semigroupNonEmpty :: Semigroup (NonEmpty a) where
35+
append (NonEmpty e1 a1) (NonEmpty e2 a2) = NonEmpty e1 (a1 <> [ e2 ] <> a2)
36+
37+
instance showNonEmpty :: Show a => Show (NonEmpty a) where
38+
show (NonEmpty e1 a1) = show e1 <> " " <> show a1
39+
40+
instance functorNonEmpty :: Functor NonEmpty where
41+
map func (NonEmpty e1 a1) = NonEmpty (func e1) (map func a1)
42+
1443
data Extended a
1544
= Finite a
1645
| Infinite
1746

47+
instance eqExtended :: Eq a => Eq (Extended a) where
48+
eq Infinite Infinite = true
49+
eq (Finite e1) (Finite e2) = e1 == e2
50+
eq _ _ = false
51+
52+
instance ordExtended :: Ord a => Ord (Extended a) where
53+
compare Infinite Infinite = EQ
54+
compare Infinite (Finite _) = GT
55+
compare (Finite _) Infinite = LT
56+
compare (Finite v1) (Finite v2) = compare v1 v2
57+
58+
instance foldableNonEmpty :: Foldable NonEmpty where
59+
foldr func st (NonEmpty val arr) = foldr func st ([ val ] <> arr)
60+
foldl func st (NonEmpty val arr) = foldl func st ([ val ] <> arr)
61+
foldMap func (NonEmpty val arr) = foldMap func ([ val ] <> arr)
62+
1863
data OneMore f a
1964
= OneMore a (f a)
2065

21-
-- instance foldableOneMore :: Foldable f => Foldable (OneMore f) where
22-
-- todo
23-
-- unsafeMaximum :: Partial => Array Int -> Int
24-
-- todo
66+
instance foldableOneMore :: Foldable f => Foldable (OneMore f) where
67+
foldr func st (OneMore val more) = func val lastb
68+
where
69+
lastb = foldr func st more
70+
foldl func st (OneMore val more) = foldl func firstb more
71+
where
72+
firstb = (func st val)
73+
foldMap func (OneMore val more) = (func val) <> (foldMap func more)
74+
75+
unsafeMaximum :: Partial => Array Int -> Int
76+
unsafeMaximum arr = case maximum arr of
77+
Just m -> m
78+
2579
class
2680
Monoid m <= Action m a where
2781
act :: m -> a -> a
@@ -35,15 +89,48 @@ instance semigroupMultiply :: Semigroup Multiply where
3589
instance monoidMultiply :: Monoid Multiply where
3690
mempty = Multiply 1
3791

38-
-- instance repeatAction :: Action Multiply String where
39-
-- todo
40-
-- instance actionArray :: Action m a => Action m (Array a) where
41-
-- todo
92+
instance actionMultiply :: Action Multiply Int where
93+
act (Multiply n) m = n * m
94+
95+
instance showMultiply :: Show Multiply where
96+
show (Multiply n) = "Multiply " <> show n
97+
98+
instance eqMultiply :: Eq Multiply where
99+
eq (Multiply n) (Multiply m) = n == m
100+
101+
instance repeatAction :: Action Multiply String where
102+
act (Multiply n) s = power s n
103+
104+
instance actionArray :: Action m a => Action m (Array a) where
105+
act m arr = map (act m) arr
106+
42107
newtype Self m
43108
= Self m
44109

110+
-- Why is Monoid constraint required here?
111+
-- Seems like this is already specified by Action class
112+
--instance actionSelf :: Action m (Self m) where
113+
instance actionSelf :: Monoid m => Action m (Self m) where
114+
act m1 (Self m2) = Self (m1 <> m2)
115+
116+
instance eqSelf :: Eq m => Eq (Self m) where
117+
eq (Self m1) (Self m2) = m1 == m2
118+
119+
instance showSelf :: Show m => Show (Self m) where
120+
show (Self m) = "Self " <> show m
121+
122+
arrayHasDuplicates :: forall a. Hashable a => Array a -> Boolean
123+
arrayHasDuplicates arr =
124+
let
125+
hashAndValEqual a b = hashEqual a b && a == b
126+
in
127+
length arr /= (length $ nubByEq hashAndValEqual arr)
128+
45129
newtype Hour
46130
= Hour Int
47131

48132
instance eqHour :: Eq Hour where
49133
eq (Hour n) (Hour m) = mod n 12 == mod m 12
134+
135+
instance hashHour :: Hashable Hour where
136+
hash (Hour h) = hash $ mod h 12

0 commit comments

Comments
 (0)