Simple problem from Hudak's SOE
Dean Herington
heringto@cs.unc.edu
Sat, 22 Feb 2003 19:16:21 -0500 (EST)
On Fri, 21 Feb 2003, M. Parker wrote:
> I'm a real newbie to Haskell, and I'm having trouble with a particular problem
> dealing with higher-order functions.
>
> Exercise 5.9 in Hudak's "School of Expression" asks us to write a function,
> "makeChange," s.t. it makes change for a given amount using coins in a coin
> supply (represented by a list of decreasing integers). For example,
> make Change 99 [5,1] ==> [19,4]
>
> This chapter is about higher order functions, so I'm assuming he wants us to
> compute the result using the higher order functions defined in the chapter
> (map, foldl, foldr). I devised two solutions:
>
> {-Solution 1-}
> makeChange money coinList =
> zipWith div (scanl mod money coinList) coinList
>
> {-Solution 2-}
> makeChange' money (coin:coins) =
> let money' = money `mod` coin
> numCoins = money `div` coin
> in (numCoins: makeChange' money' coins)
> makeChange' 0 _ = []
> makeChange' _ [] = []
>
> However, my problem is that neither solution uses the higher-order functions
> defined in the chapter. So is it possible to solve this problem using map and
> fold?
>
> Furthermore, Hudak makes the case that we should strive to find the
> higher-order solutions instead of the recursive ones because the latter leads
> to clearer and more concise solutions. Although solution 1 is more concise, I
> feel like Solution 2 is clearer to me than Solution 1, but maybe this is just
> because I'm new to haskell and higher order functions. It just seems like its
> easier to understand the actual algorithm in solution 2 than in solution 1.
>
> Thanks,
> Matt Parker
> University of North Texas undergrad
> http://www.cs.unt.edu
Here's what I had come up with for that exercise:
makeChange1 _ [] = []
makeChange1 amt (c:cs) = q : makeChange1 r cs
where (q,r) = amt `quotRem` c
makeChange2 amt coins = reverse (snd (foldl f (amt,[]) coins))
where f (amt,cnts) coin = (r,q:cnts)
where (q,r) = amt `quotRem` coin
As you said in comparing your two solutions, I'm not convinced the
higher-order solution is clearer in this case. (By the way, I do
generally like to use higher-order functions.)
Dean