Change for a Dollar is just a fun name for the Coin Change Kata where you are given an amount and you must convert that into coins.
Install Haskell
Create file change.hs
containing
module CoinChanger where
Fire up ghci and load your file (or run it with runhaskell)
% ghci
*CoinChanger> :load change
In Haskell we define our function name and types first
change :: Money -> [ Coin ]
Before TDD there was CDD (compiler driven development)
*CoinChanger> :load change
Compiler says, "You haven't implemented change
!"
change :: Money -> [ Coin ]
change = []
Compiler asks:
- What is
Money
? - What is
Coin
?
type Money = Int
type Coin = Int
change :: Money -> [ Coin ]
change = []
Complier says, "Your implementation doesn't match your signature"
change _ = []
The simplest property I can think of is the sum of change x will equal x
prop_ChangeRoundTrip m = forAll (choose (0,100)) m == sum (change m)
Compiler says, "You need parenthesis around each argument"
prop_ChangeRoundTrip m = forAll (choose (0,100)) $ m == sum (change m)
Compiler says, "The last parameter should be a function that takes a Money
and returns a Testable
"
prop_ChangeRoundTrip m = forAll (choose (0,100)) $ \m -> m == sum (change m)
import Test.QuickCheck
*CoinChanger> quickCheck prop_ChangeRoundTrip
-Red
The simplest solution to passing this test is return the amount.
change :: Money -> [ Coin ]
change m = m : []
+Green
It looks like we need to add coins
to the implementation and write another test.
coins :: [ Coin ]
coins = [25,10,5,1]
prop_ChangeContainsOnlyRealCoins m = forAll (choose (1,100)) $ \m -> all (\x -> elem x coins) $ change m
Making this pass is as simple as handing out pennies.
change :: Money -> [ Coin ]
change m = []
change m = 1 : change (m-1)
+Green
You're probably tired or running tests individually. I know I am!
Adding runTests
fixes that.
runTests = $quickCheckAll
Compiler says, "$
is a part of TemplateHaskell
, please let me know when you meta-program."
Adding the following to the top of the file will do the trick:
{-# LANGUAGE TemplateHaskell #-}
Compiler is still not happy, "quickCheckAll
! Where can I find that?"
import Test.QuickCheck.All
But how do I run all my tests?
*CoinChanger> runTests
+Green
prop_ChangeSameCoinsWillTotalLessThanNextLargerCoin = forAll (choose (0,100)) $ \m ->
let _change = change m
in all (\x -> (maxAllowedCoins coins x) >= (coinCount _change x)) $ _change
TODO Continue from here (Ignore everything below)
change :: Money -> [ Coin ]
change 0 = []
change m = largestCoin m : change (m - largestCoin m)
Compiler says, "You need to implement largestCoin
."
In TDD, we start with a test.
prop_LargestCoinPenny m = forAll (choose (1,4)) $ \m -> largestCoin m == 1
Compiler says, "You still haven't implemented largestCoin
?"
largestCoin _ = 1
Compiler says, "I am still confused! What type is largestCoin
?"
largestCoin :: Money -> Coin
largestCoin _ = 1
Are you feeling nickel and dimed, yet?
prop_LargestCoinNickel m = forAll (choose (5,9)) $ \m -> largestCoin m == 5
prop_LargestCoinDime m = forAll (choose (10,24)) $ \m -> largestCoin m == 10
Enough hard coding, lets implementation it.
largestCoin :: Money -> Coin
largestCoin m = head dropWhile (>m) [25,10,5,1]
Compiler says, "Like Clojure, I need parenthesis around dropWhile
and it's 2 args"
largestCoin m = head $ dropWhile (>m) [25,10,5,1]
coins :: [ Coin ]
coins = [25,10,5,1]
largestCoin m = head $ dropWhile (>m) coins
If someone adds a 50 cent coin to the end of coins, our code would break. We should add a property test for that.
prop_CoinsAreOrderLargestToSmallest = coins == (reverse $ sort coins)
change' = unfoldr nextCoin
where
nextCoin 0 = Nothing
nextCoin m = Just (largestCoin m, m - largestCoin m)
Compiler says, "unfoldr
? unfoldr
?! Who has heard of unfoldr
?!!"
import Data.List
Hmm... What if we got our refactor wrong? That is where QuickCheck
shines.
prop_ChangeEqualsChangePrime m = forAll (choose (0,100)) $ \m -> change m == change' m