diff --git a/exercises/nucleotide-count/examples/success-standard/src/DNA.hs b/exercises/nucleotide-count/examples/success-standard/src/DNA.hs index e1c30ce30..dac5e1d81 100644 --- a/exercises/nucleotide-count/examples/success-standard/src/DNA.hs +++ b/exercises/nucleotide-count/examples/success-standard/src/DNA.hs @@ -1,17 +1,21 @@ {-# LANGUAGE TupleSections #-} - -module DNA (nucleotideCounts) where +module DNA (nucleotideCounts, Nucleotide(..)) where import Data.Map.Strict (Map, fromDistinctAscList, fromListWith, findWithDefault) -nucleotideCounts :: String -> Either String (Map Char Int) -nucleotideCounts xs = fromDistinctAscList <$> mapM count' "ACGT" +data Nucleotide = A | C | G | T deriving (Eq, Ord, Show) + +nucleotideCounts :: String -> Either String (Map Nucleotide Int) +nucleotideCounts xs = fromDistinctAscList <$> mapM count' [A,C,G,T] where count' x = (x,) <$> occur' x occur' x = findWithDefault 0 x . countOccurrences <$> mapM valid xs countOccurrences = fromListWith (+) . flip zip (repeat 1) -valid :: Char -> Either String Char -valid x - | x `elem` "ACGT" = Right x - | otherwise = Left $ "invalid nucleotide " ++ show x +valid :: Char -> Either String Nucleotide +valid c = case c of + 'A' -> Right A + 'C' -> Right C + 'G' -> Right G + 'T' -> Right T + _ -> Left $ "Invalid nucleotide " ++ show c diff --git a/exercises/nucleotide-count/package.yaml b/exercises/nucleotide-count/package.yaml index 6263f9121..3de1f22a5 100644 --- a/exercises/nucleotide-count/package.yaml +++ b/exercises/nucleotide-count/package.yaml @@ -1,5 +1,5 @@ name: nucleotide-count -version: 1.3.0.5 +version: 1.3.0.6 dependencies: - base diff --git a/exercises/nucleotide-count/src/DNA.hs b/exercises/nucleotide-count/src/DNA.hs index 4dd7811f5..d82efd5b3 100644 --- a/exercises/nucleotide-count/src/DNA.hs +++ b/exercises/nucleotide-count/src/DNA.hs @@ -1,6 +1,8 @@ -module DNA (nucleotideCounts) where +module DNA (nucleotideCounts, Nucleotide(..)) where import Data.Map (Map) -nucleotideCounts :: String -> Either String (Map Char Int) +data Nucleotide = A | C | G | T deriving (Eq, Ord, Show) + +nucleotideCounts :: String -> Either String (Map Nucleotide Int) nucleotideCounts xs = error "You need to implement this function." diff --git a/exercises/nucleotide-count/test/Tests.hs b/exercises/nucleotide-count/test/Tests.hs index 33620b414..07fb67975 100644 --- a/exercises/nucleotide-count/test/Tests.hs +++ b/exercises/nucleotide-count/test/Tests.hs @@ -5,7 +5,7 @@ import Data.Map (fromList) import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy) import Test.Hspec.Runner (configFastFail, defaultConfig, hspecWith) -import DNA (nucleotideCounts) +import DNA (nucleotideCounts, Nucleotide(..)) main :: IO () main = hspecWith defaultConfig {configFastFail = True} specs @@ -18,29 +18,29 @@ specs = do describe "nucleotideCounts" $ do it "empty dna strand has no nucleotides" $ - nucleotideCounts "" `matchesMap` [ ('A', 0) - , ('C', 0) - , ('G', 0) - , ('T', 0) ] + nucleotideCounts "" `matchesMap` [ (A, 0) + , (C, 0) + , (G, 0) + , (T, 0) ] it "can count one nucleotide in single-character input" $ - nucleotideCounts "G" `matchesMap` [ ('A', 0) - , ('C', 0) - , ('G', 1) - , ('T', 0) ] + nucleotideCounts "G" `matchesMap` [ (A, 0) + , (C, 0) + , (G, 1) + , (T, 0) ] it "repetitive-sequence-has-only-guanosine" $ - nucleotideCounts "GGGGGGGG" `matchesMap` [ ('A', 0) - , ('C', 0) - , ('G', 8) - , ('T', 0) ] + nucleotideCounts "GGGGGGGG" `matchesMap` [ (A, 0) + , (C, 0) + , (G, 8) + , (T, 0) ] it "counts all nucleotides" $ nucleotideCounts "AGCTTTTCATTCTGACTGCAACGGGCAATATGTCTCTGTGTGGATTAAAAAAAGAGTGTCTGATAGCAGC" - `matchesMap` [ ('A', 20) - , ('C', 12) - , ('G', 17) - , ('T', 21) ] + `matchesMap` [ (A, 20) + , (C, 12) + , (G, 17) + , (T, 21) ] it "validates strand" $ nucleotideCounts "AGXXACT" `shouldSatisfy` isLeft