[Haskell-cafe] Re: Coin changing algorithm

ChrisK chrisk at MIT.EDU
Thu Jul 14 17:19:23 EDT 2005


The combinator is really elegant, but I want to ask a question about the
arrays that get built.  The 3D array index is by (m,n,i) and a single
array should be good for all of the results.

If I say let {x=change 10 5; y=change 5 10;} then it looks like "dp
(10,5,8)" and "dp (5,10,8)" get evaluated.  These seem to define two
arrays , "array (10,5,8)" and "array (5,10,8)".

I know that that the arrays share a common subset, but I am wondering:
does Haskell (as opposed to an specific compiler, e.g. GHC) realize that?

During a single evaluation the recursive calls never "collide", so
unless this overlap is optimized, then the subproblem memoizing won't do
anything...

-- 
Chris


Okasaki, C. DR EECS wrote:
> This is a classic dynamic programming problem.  Dynamic programming is
> easy to do in Haskell using recursive arrays.  Instead of using
> recursive arrays directly, however, I'll add a few helper functions that
> make this kind of problem easier.
> 
> 
>>import Array
>>
>>tabulate :: (Ix a) => (a,a) -> (a -> b) -> Array a b
>>tabulate bounds f = array bounds [(i,f i) | i <- range bounds]
>>
>>dp :: (Ix a) => (a,a) -> ((a->b) -> a -> b) -> a -> b
>>dp bounds f = (memo!) where
>>  memo = tabulate bounds (f (memo!))
> 
> 
> 'tabulate' just turns a function into an array. 'dp' is a memoizing Y
> combinator.  That is, you give the same kind of almost recursive
> function you would give to the Y combinator, and it "ties the knot" for
> you, but also interposes an array to hold the intermediate results.
> 
> (What do I mean by an "almost recursive function"?  I mean that instead
> of writing a recursive function "f = ...f...", you instead write f to
> take what will end up being the recursive function as its first
> argument.  Then, whenever the f would normally call itself, it instead
> calls this argument, as in "f rec = ...rec...".)
> 
> Now, here is the change algorithm, using esentially the same recursion
> as Radu, except that I introduce an 'i' parameter, that is the index of
> the largest denomination that you are allowed to use.  (Using this
> parameter makes it easier to store the results in an array than passing
> around a list of the available coins.)
> 
> 
>>change m n = dp bounds f (m,n,8) where
>>  bounds = ((0,0,0), (m,n,8))
>>  coins = listArray (1,8) [1,2,5,10,20,50,100,200]
>>  f rec (m,n,i)
>>    | m == 0 = [[]]
>>    | n == 0 || i == 0 = []
>>    | c > m = rec (m,n,i-1)
>>    | otherwise = map (c:) (rec (m-c,n-1,i)) ++ rec (m,n,i-1)
>>    where c = coins!i
> 
> 
> In the f function, m is the amount of change to make, n is the number of
> coins that can be used, and i is the highest kind of coin that you are
> allowed to use.  
> 
> You can do most traditional dynamic programming problems this way.
> 
> Enjoy,
> Chris
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list