Simon Peyton-Jones wrote:
1. Small examples of actual code.

I particularly like the lazy way of counting change example (also works for picking items off a menu).

The code below show 3 approaches :
 a function for computing the coins used in each way as a verbose list
 a function for computing just the total number of ways
 a simply Monoid that does both at once, which a pretty summary display
And it has a short but user friendly main function that drives it.

The method used is simple. It considers each value of coin in turn, this loop is done by the foldr. The value being folded is a list where the index into the list is an amount for which change is being made; the value at that list index is the list or count of the ways to make that amount using the coins considered so far.

These exploit laziness since the returned lists are infinite and since 'result' is defined recursively for each different value of coin.

The example of defining a Monoid is a clear abstraction or generalization of the first two functions.

-- This demonstrates a way to find every eay to make change for a
-- given total using a set of coins.
--
-- By Chris Kuklewicz, Public Domain
import System.Environment(getArgs)
import Control.Exception as E(catch)
import Control.Monad(when)
import Data.List(group)
import Data.Monoid(Monoid(mempty,mappend))

computeListOfWays :: [Int] -> [[[Int]]]
computeListOfWays coins = foldr includeValue noValues coins
  where noValues = [] : repeat []
        includeValue value oldResult =
          let (unchangedResult,changedResult) = splitAt value oldResult
              result = unchangedResult ++
                       zipWith (++) changedResult (map addCoin result)
              addCoin = map (value:)
          in result

computeCountOfWays :: [Int] -> [Integer]
computeCountOfWays coins = foldr includeValue noValues coins
  where noValues = 1 : repeat 0
        includeValue value oldResult =
          let (unchangedResult,changedResult) = splitAt value oldResult
              result = unchangedResult ++
                       zipWith (+) changedResult result
          in result

computeWays :: [Int] -> [Ways]
computeWays coins = foldr includeValue noValues coins
  where noValues = Ways [[]] 1 : repeat mempty
        includeValue value oldResult =
          let (unchangedResult,changedResult) = splitAt value oldResult
              result = unchangedResult ++
                       zipWith mappend changedResult (map addCoin result)
              addCoin (Ways list count) = Ways (map (value:) list) count
          in result

data Ways = Ways [[Int]] Integer

instance Monoid Ways where
  mempty = Ways [] 0
  mappend (Ways list1 count1) (Ways list2 count2) = Ways (list1++list2) 
(count1+count2)

instance Show Ways where
  show (Ways list count) = unlines (map summary list) ++ "Count of Ways = " ++ show count 
++ "\n"
    where summary = show . map (\sub -> (length sub,head sub)) . group


coins_US :: [Int]
coins_US = [1,5,10,25,50]

coins_UK :: [Int]
coins_UK = [1,2,5,10,20,50]

main = do
  args <- getArgs
  case args of
    [] -> error "Pass a number of cents for which to count ways of making 
change"
    [x] -> do n <- E.catch (readIO x) (const (error "The argument passed needs to be 
a number"))
              when (n<0) (error "The argument passed needs to be a non-negative 
number")
              print (computeWays coins_US !! n)
    _ -> error "Too many parameters, need just one number"

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to