Skip to content

Commit 3da8c2f

Browse files
Ch4 solutions (#107)
* formatted solutions * Add solution for additional filtering tests Co-authored-by: oldfartdeveloper <scottnelsonsmith@gmail.com>
1 parent 1fb43e4 commit 3da8c2f

File tree

2 files changed

+151
-5
lines changed

2 files changed

+151
-5
lines changed

exercises/chapter4/test/Main.purs

Lines changed: 19 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,25 @@ import Data.Maybe (Maybe(..))
55
import Data.Path (filename, root)
66
import Data.Tuple (fst)
77
import Effect (Effect)
8+
import Test.Solutions
9+
( allTrue
10+
, cartesianProduct
11+
, evenCount
12+
, exclusiveOrThenTrue
13+
, factorizations
14+
, fib
15+
, isEven
16+
, isPrime
17+
, keepNonNegative
18+
, keepNonNegativeRewrite
19+
, largestSmallest
20+
, onlyFiles
21+
, reverse
22+
, squared
23+
, triples
24+
, whereIs
25+
, (<$?>)
26+
)
827
import Test.Unit (suite, test)
928
import Test.Unit.Assert as Assert
1029
import Test.Unit.Main (runTest)
@@ -14,8 +33,6 @@ main =
1433
runTest do
1534
test "Initial passing test"
1635
$ Assert.equal true true
17-
18-
{- Move this block comment starting point to enable more tests
1936
suite "Exercise Group 1" do
2037
suite "Exercise 1 - Test if integer is even" do
2138
test "0 is even"
@@ -183,4 +200,3 @@ main =
183200
test "doesn't locate a file"
184201
$ Assert.equal (Nothing)
185202
$ whereIs "lss"
186-
-}
Lines changed: 132 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,21 +1,151 @@
11
module Test.Solutions where
22

33
import Prelude
4-
import Data.Array ((:), (..))
5-
import Data.Path (Path, ls)
4+
import Data.String.Pattern (Pattern(..))
5+
import Data.Foldable (foldl)
6+
import Data.Int (rem, quot)
7+
import Data.Path (Path(), filename, isDirectory, ls, root, size)
8+
import Data.Array (cons, filter, head, last, length, tail, (:), (..))
9+
import Data.Maybe (Maybe(..), fromMaybe, maybe)
10+
import Data.String.Common (split)
11+
import Data.Tuple (Tuple(..), snd)
612
import Control.MonadZero (guard)
713

14+
isEven :: Int -> Boolean
15+
isEven n = case n of
16+
0 -> true
17+
1 -> false
18+
_ -> isEven $ n - 2
19+
20+
oneIfEven :: Int -> Int
21+
oneIfEven n = if isEven n then 1 else 0
22+
23+
evenCount :: Array Int -> Int
24+
evenCount ints = evenCount' ints 0
25+
where
26+
evenCount' :: Array Int -> Int -> Int
27+
evenCount' [] count = count
28+
29+
evenCount' ints' count = evenCount' (fromMaybe [] (tail ints')) $ add count $ maybe 0 oneIfEven $ head ints'
30+
31+
squared :: Array Number -> Array Number
32+
squared arr = map (\n -> n * n) arr
33+
34+
keepNonNegative :: Array Number -> Array Number
35+
keepNonNegative arr = filter (\n -> n >= 0.0) arr
36+
37+
infix 4 filter as <$?>
38+
39+
keepNonNegativeRewrite :: Array Number -> Array Number
40+
keepNonNegativeRewrite arr = (\n -> n >= 0.0) <$?> arr
41+
842
factors :: Int -> Array (Array Int)
943
factors n = do
1044
i <- 1 .. n
1145
j <- i .. n
1246
guard $ i * j == n
1347
pure [ i, j ]
1448

49+
isPrime :: Int -> Boolean
50+
isPrime n = eq 1 $ length $ factors n
51+
52+
cartesianProduct :: a. Array a -> Array a -> Array (Array a)
53+
cartesianProduct left right = do
54+
a_ <- left
55+
b_ <- right
56+
[ [ a_, b_ ] ]
57+
58+
triples :: Int -> Array (Array Int)
59+
triples n = do
60+
i <- 1 .. n
61+
j <- i .. n
62+
k <- j .. n
63+
guard $ i * i + j * j == k * k
64+
pure [ i, j, k ]
65+
66+
-- | Provide the prime numbers that, multiplied together, make the argument.
67+
factorizations :: Int -> Array Int
68+
factorizations n = factorizations' 2 n []
69+
where
70+
factorizations' :: Int -> Int -> Array Int -> Array Int
71+
factorizations' _ 1 result = result
72+
73+
factorizations' divisor dividend result =
74+
let
75+
remainder = rem dividend divisor
76+
in
77+
if remainder == 0 then
78+
factorizations' (divisor) (quot dividend divisor) (cons divisor result)
79+
else
80+
factorizations' (divisor + 1) dividend result
81+
82+
allTrue :: Array Boolean -> Boolean
83+
allTrue bools = foldl (\acc bool -> acc && bool) true bools
84+
85+
exclusiveOrThenTrue :: Array Boolean -> Boolean
86+
exclusiveOrThenTrue bools = foldl (==) false bools
87+
88+
-- | The fib routine in tail recursive form
89+
fib :: Int -> Int
90+
fib n = fib' n 0 0 1
91+
where
92+
fib' :: Int -> Int -> Int -> Int -> Int
93+
fib' limit count n1 n2 =
94+
if limit == count then
95+
n1 + n2
96+
else
97+
fib' limit (count + 1) (n1 + n2) n1
98+
99+
reverse :: a. Array a -> Array a
100+
reverse = foldl (\xs x -> [ x ] <> xs) []
101+
15102
-- Section for : A Virtual Filesystem exercise
16103
allFiles :: Path -> Array Path
17104
allFiles file =
18105
file
19106
: do
20107
child <- ls file
21108
allFiles child
109+
110+
onlyFiles :: Path -> Array Path
111+
onlyFiles p = filter (\p' -> not $ isDirectory p') $ allFiles p
112+
113+
maxSigned32BitInt :: Int
114+
maxSigned32BitInt = 2147483647
115+
116+
largestSmallest :: Path -> Array (Tuple String Int)
117+
largestSmallest path = largestSmallestPaths (allFiles path)
118+
where
119+
largestSmallestPaths :: Array Path -> Array (Tuple String Int)
120+
largestSmallestPaths paths = [ outlier (\i j -> i > j) 0 paths, outlier (\i j -> i < j) maxSigned32BitInt paths ]
121+
where
122+
outlier :: (Int -> Int -> Boolean) -> Int -> Array Path -> Tuple String Int
123+
outlier criteria startValue paths' =
124+
foldl
125+
( \acc p' ->
126+
( case size p' of
127+
Just n -> if criteria n $ snd acc then Tuple (filename p') n else acc
128+
Nothing -> acc
129+
)
130+
)
131+
(Tuple "" startValue)
132+
paths'
133+
134+
allSizes :: Array Path -> Array (Tuple String Int)
135+
allSizes paths =
136+
map
137+
( \p -> case size p of
138+
Just n -> Tuple (filename p) n
139+
Nothing -> Tuple (filename p) 0
140+
)
141+
paths
142+
143+
whereIs :: String -> Maybe String
144+
whereIs fileName = head $ whereIs' $ allFiles root
145+
where
146+
whereIs' :: Array Path -> Array String
147+
whereIs' paths = do
148+
path <- paths
149+
child <- ls path
150+
guard $ eq fileName $ fromMaybe "" $ last $ split (Pattern "/") $ filename child
151+
pure $ filename path

0 commit comments

Comments
 (0)