Examples of different syntaxes for function application in validators
This commit is contained in:
parent
05e4a3f552
commit
7699137716
@ -1,39 +1,48 @@
|
|||||||
module Homework.Ch01 where
|
module Homework.Ch01 where
|
||||||
|
|
||||||
-- This calls reverse on toDigitsRev because I somehow did this backwards by default.
|
|
||||||
toDigits :: Integer -> [Integer]
|
toDigits :: Integer -> [Integer]
|
||||||
toDigits = rev [] . toDigitsRev
|
toDigits = go []
|
||||||
where
|
where
|
||||||
rev acc (x : xs) = rev (x : acc) xs
|
go acc 0 = acc
|
||||||
rev acc [] = acc
|
go acc n = go (n `mod` 10 : acc) (n `div` 10)
|
||||||
|
|
||||||
|
revDigits :: [Integer] -> [Integer]
|
||||||
|
revDigits = go []
|
||||||
|
where
|
||||||
|
go acc (x : xs) = go (x : acc) xs
|
||||||
|
go acc [] = acc
|
||||||
|
|
||||||
-- I don't know how I managed it, but turning the number into an array already reversed it?
|
|
||||||
toDigitsRev :: Integer -> [Integer]
|
toDigitsRev :: Integer -> [Integer]
|
||||||
toDigitsRev n
|
toDigitsRev = revDigits . toDigits
|
||||||
| n < 1 = []
|
|
||||||
| otherwise =
|
|
||||||
let leftDigit = n `mod` 10
|
|
||||||
shiftedDigits = n `div` 10
|
|
||||||
in leftDigit : toDigitsRev shiftedDigits
|
|
||||||
|
|
||||||
doubleEveryOther :: [Integer] -> [Integer]
|
doubleEveryOther :: [Integer] -> [Integer]
|
||||||
doubleEveryOther (odd' : even' : rest) = odd' : (even' * 2) : doubleEveryOther rest
|
doubleEveryOther = revDigits . go []
|
||||||
doubleEveryOther rest = rest
|
where
|
||||||
|
go acc (first : second : rest) = go ((second * 2) : first : acc) rest
|
||||||
|
go acc [last'] = last' : acc
|
||||||
|
go acc [] = acc
|
||||||
|
|
||||||
sumDigits :: [Integer] -> Integer
|
sumDigits :: [Integer] -> Integer
|
||||||
sumDigits = sumDigits' 0 . flattenDigits [] . eachToDigits []
|
sumDigits = sumDigits' . flattenDigits . eachToDigits
|
||||||
where
|
where
|
||||||
eachToDigits acc (x : xs) = eachToDigits (toDigits x : acc) xs
|
eachToDigits = foldDigits [] (\n acc -> toDigits n : acc)
|
||||||
eachToDigits acc [] = acc
|
flattenDigits = foldDigits [] (++)
|
||||||
|
sumDigits' = foldDigits 0 (+)
|
||||||
|
|
||||||
flattenDigits acc ((x : xs) : rest) = flattenDigits (x : acc) (xs : rest)
|
foldDigits acc f (x : xs) = foldDigits (f x acc) f xs
|
||||||
flattenDigits acc ([] : rest) = flattenDigits acc rest
|
foldDigits acc _ [] = acc
|
||||||
flattenDigits acc [] = acc
|
|
||||||
|
|
||||||
sumDigits' acc (x : xs) = sumDigits' (acc + x) xs
|
validateWithParens :: Integer -> Bool
|
||||||
sumDigits' acc [] = acc
|
validateWithParens n = f n `mod` 10 == 0
|
||||||
|
where
|
||||||
|
f n' = sumDigits (doubleEveryOther (toDigitsRev n'))
|
||||||
|
|
||||||
validate :: Integer -> Bool
|
validateWithDollars :: Integer -> Bool
|
||||||
validate n = f n `mod` 10 == 0
|
validateWithDollars n = f n `mod` 10 == 0
|
||||||
|
where
|
||||||
|
f n' = sumDigits $ doubleEveryOther $ toDigitsRev n'
|
||||||
|
|
||||||
|
validateWithCompose :: Integer -> Bool
|
||||||
|
validateWithCompose n = f n `mod` 10 == 0
|
||||||
where
|
where
|
||||||
f = sumDigits . doubleEveryOther . toDigitsRev
|
f = sumDigits . doubleEveryOther . toDigitsRev
|
||||||
|
@ -44,10 +44,38 @@ spec = describe "Credit Card Validation" $ do
|
|||||||
it "splits doubled digits into single digits and sums all single digits together" $ do
|
it "splits doubled digits into single digits and sums all single digits together" $ do
|
||||||
sumDigits [16, 7, 12, 5] `shouldBe` 22
|
sumDigits [16, 7, 12, 5] `shouldBe` 22
|
||||||
|
|
||||||
describe "validate" $ do
|
context "validators" $ do
|
||||||
it "returns True for a valid credit card number" $ do
|
let validators =
|
||||||
validate 5105105105105100 `shouldBe` True
|
[ ("validateWithParens", validateWithParens),
|
||||||
validate 2223577120017656 `shouldBe` True
|
("validateWithDollars", validateWithDollars),
|
||||||
it "returns False for invalid credit card number" $ do
|
("validateWithCompose", validateWithCompose)
|
||||||
validate 5105105105105101 `shouldBe` False
|
]
|
||||||
validate 2223573420017656 `shouldBe` False
|
|
||||||
|
accept num = (num, True)
|
||||||
|
reject num = (num, False)
|
||||||
|
labelExpectation num expectIsValid
|
||||||
|
| expectIsValid = "accepts " ++ show num
|
||||||
|
| otherwise = "rejects " ++ show num
|
||||||
|
|
||||||
|
nums =
|
||||||
|
[ accept 5105105105105100,
|
||||||
|
accept 2223577120017656,
|
||||||
|
accept 371449635398431,
|
||||||
|
accept 6011000990139424,
|
||||||
|
accept 30569309025904,
|
||||||
|
accept 3566002020360505,
|
||||||
|
reject 5105105105105101,
|
||||||
|
reject 5420933878724339,
|
||||||
|
reject 5506923616306249,
|
||||||
|
reject 3999292939485618
|
||||||
|
]
|
||||||
|
|
||||||
|
runExpectation validate' num expectedResult =
|
||||||
|
it (labelExpectation num expectedResult) $ do
|
||||||
|
validate' num `shouldBe` expectedResult
|
||||||
|
|
||||||
|
runValidator label validate' =
|
||||||
|
describe label $ do
|
||||||
|
sequence_ (uncurry (runExpectation validate') <$> nums)
|
||||||
|
|
||||||
|
sequence_ (uncurry runValidator <$> validators)
|
||||||
|
Loading…
Reference in New Issue
Block a user