Skip to content

Commit e83dfd0

Browse files
committed
Changing return type of Nucleotide Count to Either
By using an `Either` instead of throwing an error, the resulting exercise is more idiomatic to Haskell. The `Either` will provide a useful error message to end users of the functions. Closes exercism#157
1 parent 62fc8a7 commit e83dfd0

File tree

2 files changed

+25
-32
lines changed

2 files changed

+25
-32
lines changed

exercises/nucleotide-count/example.hs

Lines changed: 15 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -1,19 +1,20 @@
11
module DNA (count, nucleotideCounts) where
2-
import Data.Map.Strict (Map, fromListWith)
32

4-
count :: Char -> String -> Int
5-
count needle = length . filter (nucleotide ==) . map verifyDNA
6-
where nucleotide = verifyDNA needle
3+
import qualified Control.Applicative as A
4+
import Data.Map.Strict (Map, (!), fromDistinctAscList, fromListWith, findWithDefault)
75

8-
nucleotideCounts :: String -> Map Char Int
9-
nucleotideCounts strand = fromListWith (+) (defaults ++ map pair strand)
10-
where defaults = zip dna (repeat 0)
11-
pair nucleotide = (verifyDNA nucleotide, 1)
6+
count :: Char -> String -> Either String Int
7+
count x xs = (!) A.<$> nucleotideCounts xs A.<*> valid x
128

13-
dna :: String
14-
dna = "ACGT"
9+
nucleotideCounts :: String -> Either String (Map Char Int)
10+
nucleotideCounts xs = fromDistinctAscList A.<$> mapM count' "ACGT"
11+
where
12+
count' x = (\c -> (x, c)) A.<$> occur' x
13+
occur' x = findWithDefault 0 x . countOccurrences A.<$> mapM valid xs
14+
countOccurrences = fromListWith (+) . flip zip (repeat 1)
15+
16+
valid :: Char -> Either String Char
17+
valid x
18+
| x `elem` "ACGT" = Right x
19+
| otherwise = Left $ "invalid nucleotide " ++ show x
1520

16-
verifyDNA :: Char -> Char
17-
verifyDNA nucleotide | nucleotide `elem` dna = nucleotide
18-
| otherwise = error ("invalid nucleotide " ++
19-
show nucleotide)
Lines changed: 10 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1,21 +1,13 @@
1-
import Test.HUnit (Assertion, (@=?), runTestTT, assertFailure, Test(..), Counts(..))
1+
import Test.HUnit (Assertion, (@=?), runTestTT, Test(..), Counts(..))
22
import System.Exit (ExitCode(..), exitWith)
33
import DNA (count, nucleotideCounts)
44
import Data.Map (fromList)
5-
import qualified Control.Exception as E
65

76
exitProperly :: IO Counts -> IO ()
87
exitProperly m = do
98
counts <- m
109
exitWith $ if failures counts /= 0 || errors counts /= 0 then ExitFailure 1 else ExitSuccess
1110

12-
assertError :: String -> a -> IO ()
13-
assertError err f =
14-
do r <- E.try (E.evaluate f)
15-
case r of
16-
Left (E.ErrorCall s) | err == s -> return ()
17-
_ -> assertFailure ("expecting error " ++ show err)
18-
1911
testCase :: String -> Assertion -> Test
2012
testCase label assertion = TestLabel label (TestCase assertion)
2113

@@ -27,29 +19,29 @@ main = exitProperly $ runTestTT $ TestList
2719
countTests :: [Test]
2820
countTests =
2921
[ testCase "empty dna strand has no adenosine" $
30-
0 @=? count 'A' ""
22+
Right 0 @=? count 'A' ""
3123
, testCase "repetitive cytidine gets counted" $
32-
5 @=? count 'C' "CCCCC"
24+
Right 5 @=? count 'C' "CCCCC"
3325
, testCase "counts only thymidine" $
34-
1 @=? count 'T' "GGGGGTAACCCGG"
26+
Right 1 @=? count 'T' "GGGGGTAACCCGG"
3527
, testCase "validates nucleotides" $
36-
assertError "invalid nucleotide 'X'" $ count 'X' "GACT"
28+
Left "invalid nucleotide 'X'" @=? count 'X' "GACT"
3729
, testCase "validates strand" $
38-
assertError "invalid nucleotide 'Y'" $ count 'G' "GACYT"
30+
Left "invalid nucleotide 'Y'" @=? count 'G' "GACYT"
3931
]
4032

4133
nucleotideCountTests :: [Test]
4234
nucleotideCountTests =
4335
[ testCase "empty dna strand has no nucleotides" $
44-
fromList [('A', 0), ('T', 0), ('C', 0), ('G', 0)] @=?
36+
Right (fromList [('A', 0), ('T', 0), ('C', 0), ('G', 0)]) @=?
4537
nucleotideCounts ""
4638
, testCase "repetitive-sequence-has-only-guanosine" $
47-
fromList [('A', 0), ('T', 0), ('C', 0), ('G', 8)] @=?
39+
Right (fromList [('A', 0), ('T', 0), ('C', 0), ('G', 8)]) @=?
4840
nucleotideCounts "GGGGGGGG"
4941
, testCase "counts all nucleotides" $
50-
fromList [('A', 20), ('T', 21), ('C', 12), ('G', 17)] @=?
42+
Right (fromList [('A', 20), ('T', 21), ('C', 12), ('G', 17)]) @=?
5143
nucleotideCounts ("AGCTTTTCATTCTGACTGCAACGGGCAATATGTCTCTGTGTGGATTAAAAAAA" ++
5244
"GAGTGTCTGATAGCAGC")
5345
, testCase "validates strand" $
54-
assertError "invalid nucleotide 'P'" $ nucleotideCounts "GPAC"
46+
Left "invalid nucleotide 'P'" @=? nucleotideCounts "GPAC"
5547
]

0 commit comments

Comments
 (0)