
Anyone please tell me what is wrong with the function: isEmpty ::[a]->Bool isEmpty xs | xs == [] = True |otherwise =False When I tried to load it into the interpreter,it says the following: Could not deduce (Eq a) from the context () arising from use of `==' at mylab2.hs:16 Probable fix: Add (Eq a) to the type signature(s) for `isEmpty' In a pattern guard for the definition of `isEmpty': xs == [] In the definition of `isEmpty': isEmpty xs | xs == [] = True -- X.W.D

On Tue, 12 Jul 2005, wenduan wrote:
Anyone please tell me what is wrong with the function:
isEmpty ::[a]->Bool isEmpty xs | xs == [] = True |otherwise =False When I tried to load it into the interpreter,it says the following:
Could not deduce (Eq a) from the context () arising from use of `==' at mylab2.hs:16
It means that the comparison with (==) only works for types of the Eq class. This also applies to comparison with the empty list because there are different types of empty lists. Thus you have to write isEmpty :: Eq a => [a] -> Bool But it is a bad solution. Better is isEmpty [] = True isEmpty _ = False or even better: Use the standard function 'null'.

Hi, The problem is: Given an amount of money m, and unlimited coins of value 1p, 2p, 5p, 10p, 20p, 50p, £1 and £2 List ALL (distinct) ways of change for m, using no greater than k coins eg: m = 75, k = 5 => [50, 20, 5] [50, 20, 1,2,2] .......... ......... i have been familiar with the "integer parition" problem, but how to generalise to solve the one above ? Is this problem suitable for functional programming language ? Any idea ? Cheers _________________________________________________________________ It's fast, it's easy and it's free. Get MSN Messenger 7.0 today! http://messenger.msn.co.uk

On Wed, 13 Jul 2005, Dinh Tien Tuan Anh wrote: (snip)
eg: m = 75, k = 5 => [50, 20, 5] [50, 20, 1,2,2] (snip) Is this problem suitable for functional programming language ?
Oh, what fun. I like this sort of thing. My quick attempt is: module Coins where import Data.Maybe nextChange :: Num a => (Int, [a]) -> [(Int, [a])] nextChange (n, xs) = [ (n', increment n' xs) | n' <- [ n .. length xs - 1 ] ] where increment 0 (x:xs) = x+1 : xs increment n (x:xs) = x : increment (n-1) xs makeChange :: (Num a, Ord a) => [a] -> a -> a -> [[a]] makeChange coins total number = helper (0, replicate (length coins) 0) where helper state@(_, change) | sum change > number = [] -- too many coins | otherwise = case compare (sum (zipWith (*) coins change)) total of EQ -> [change] -- correct amount LT -> concatMap helper (nextChange state) -- too little GT -> [] -- too much showResults :: Num a => [a] -> [a] -> [String] showResults coins change = mapMaybe showResult (zip coins change) where showResult (_,0) = Nothing showResult (c,n) = Just (show n ++ " x " ++ show c) test = let coins = [1,2,5,10,20,50,100,200] printChange change = do mapM_ putStrLn (showResults coins change) putChar '\n' in mapM_ printChange (makeChange coins 75 5) I post it here because, whenever I do, someone else shows a much better solution that's shorter and clearer! Especially, I don't see myself using much real functional programming in the above, and I'd love to see a better approach. -- Mark

Mark Carroll
On Wed, 13 Jul 2005, Dinh Tien Tuan Anh wrote:
(snip)
eg: m = 75, k = 5 => [50, 20, 5] [50, 20, 1,2,2] (snip) Is this problem suitable for functional programming language ?
Oh, what fun. I like this sort of thing. My quick attempt is:
Just for more fun, here is my solution for all the partitions of all Ints. Yes, I really used it for real work (quantum field theory, heh). There is no limit on the lengths, but that could be easily added, I think. And it's fully memoized. Here we go:
partitions :: [[[Int]]] partitions = [[]]:[[n]:concat [map (m:) $ dropWhile ((m<).head) pars | (m,pars) <- zip [n-1,n-2..1] (tail partitions)] | n <- [1..]] -- Feri.

On 7/13/05, Dinh Tien Tuan Anh
Any idea ?
This is the first thing I wrote when i read your problem: === begin integer_partition.lhs === This is a solution to a question asked on Haskell cafe. The problem looks like a classical one. You are given a list of positive integers and integers m and n. You are to find all multisets with at most k elements from the given list that sum up to m. The idea is to write a recursive function that divides the problem into finding multisets with various maximal elements.
partition :: [Int] -> Int -> Int -> [[Int]]
The base case with exactly one solution
partition _ m _ | m == 0 = [[]]
The base cases with no solution
partition [] _ _ = [] partition _ m _ | m < 0 = [] partition _ _ k | k <= 0 = []
Now we are prepared to attack the general case:
partition (x:xs) m k = (prefix x (partition (x:xs) (m-x) (pred k))) ++ (partition xs m k)
The prefix function simply prepends a value to every list.
prefix :: Int -> [[Int]] -> [[Int]] prefix x = map (\xs -> x:xs)
Now, how to memoize this one? As is it is a SLOW solution. === end integer_partition.lhs === -- regards, radu http://rgrig.blogspot.com/

Well, I don't have time to do more than comment, but here are few improvements: Sort the list of integers, highest at the front of the list. (And perhaps remove duplicates with nub) When you pop the first element you can already compute the range of quantity you will need, and can perhaps special case when only zero quantity will be permitted (untested): partition (x:xs) m k | x>m = partition xs m k -- x is too big partition (x:xs) m k | otherwise = let most = min k (div m x) range = [most,most-1..1] use quantity = (\quantity -> prefix (replicate quantity x) (partition xs (m-quantity*x) (k-quantity)) in map use range The first result from this will be the greediest. Radu Grigore wrote:
On 7/13/05, Dinh Tien Tuan Anh
wrote: Any idea ?
This is the first thing I wrote when i read your problem:
=== begin integer_partition.lhs === This is a solution to a question asked on Haskell cafe. The problem looks like a classical one.
You are given a list of positive integers and integers m and n. You are to find all multisets with at most k elements from the given list that sum up to m.
The idea is to write a recursive function that divides the problem into finding multisets with various maximal elements.
partition :: [Int] -> Int -> Int -> [[Int]]
The base case with exactly one solution
partition _ m _ | m == 0 = [[]]
The base cases with no solution
partition [] _ _ = [] partition _ m _ | m < 0 = [] partition _ _ k | k <= 0 = []
Now we are prepared to attack the general case:
partition (x:xs) m k = (prefix x (partition (x:xs) (m-x) (pred k))) ++ (partition xs m k)
The prefix function simply prepends a value to every list.
prefix :: Int -> [[Int]] -> [[Int]] prefix x = map (\xs -> x:xs)
Now, how to memoize this one? As is it is a SLOW solution. === end integer_partition.lhs ===

On 7/13/05, ChrisK
Sort the list of integers, highest at the front of the list. (And perhaps remove duplicates with nub)
The first time I wrote in the comments that 'partition' takes a "decreasing list of integers..." and then I decided to drop "decreasing". Weakest precondition :)
When you pop the first element you can already compute the range of quantity you will need,
Is that really faster? I wouldn't be sure without profiling.. -- regards, radu http://rgrig.blogspot.com/

Of course I can't be sure about speed. If you make a recursive call it will need to check all the guarded cases, by computing the range of quantity it is doing the same work one additional time to get most, but then avoid the work of checking the final failing case that the other solutions relied on. So profiling is definately needed since it moves the work of checking the guard, not changes it. BUG: I wrote "prefix" where I needed to write "concat". And I left the base cases off, since others have already shown what they are. If you wanted a different return type using (coin,quantity) tuples, then you could change (replicate quantity x) to (x,quantity) and use "prefix". Starting with the largest quantity makes it return the results in reverse order to most of the other examples, which may or may not be what is wanted. Assuming sorted unique coins means I don't need Cale's (filter (<= x coins)) over and over again. Radu Grigore wrote:
On 7/13/05, ChrisK
wrote: Sort the list of integers, highest at the front of the list. (And perhaps remove duplicates with nub)
The first time I wrote in the comments that 'partition' takes a "decreasing list of integers..." and then I decided to drop "decreasing". Weakest precondition :)
When you pop the first element you can already compute the range of quantity you will need,
Is that really faster? I wouldn't be sure without profiling..

Okay, I like Cale's extra guard short circuit so much I must add it to my pseudo-example. Cale's guard:
amount `div` maximum coins > maxCoins = [] -- optimisation
Mine, updated.
partition (x:xs) m k | x>m = partition xs m k -- x is too big
parititon (x:_) m k | x*k < m = [] -- cannot succeed
partition (x:xs) m k | otherwise = let most = min k (div m x) range = [most,most-1..1] use quantity = (\quantity -> prefix (replicate quantity x) (partition xs (m-quantity*x) (k-quantity)) in map use range
The first result from this will be the greediest.
As for memoizing, it would be interesting to attack it differently. Get all the results for a given m and unlimited k and store them sorted by k. Then return the list via takeWhile length up to k. Next call for same m can skip to the takeWhile and be very fast. Pre-generating the table for amounts up to some limit could be done more efficiently with a bottom up approach. -- Chris

Here's my little recursive solution:
import Monad
import List
makeChange :: [Integer] -> Integer -> Integer -> [[Integer]]
makeChange coins amount maxCoins
| amount < 0 = []
| amount == 0 = [[]]
| null coins = []
| amount `div` maximum coins > maxCoins = [] -- optimisation
| amount > 0 =
do x <- coins
xs <- makeChange (filter (<= x) coins)
(amount - x)
(maxCoins - 1)
guard (genericLength (x:xs) <= maxCoins)
return (x:xs)
makeChange' :: Integer -> Integer -> [[Integer]]
makeChange' amount maxCoins = makeChange coins amount maxCoins
where coins = [200,100,50,20,10,5,2,1]
-- Cale
On 13/07/05, Dinh Tien Tuan Anh
Hi, The problem is: Given an amount of money m, and unlimited coins of value 1p, 2p, 5p, 10p, 20p, 50p, £1 and £2 List ALL (distinct) ways of change for m, using no greater than k coins
eg: m = 75, k = 5 => [50, 20, 5] [50, 20, 1,2,2] .......... .........
i have been familiar with the "integer parition" problem, but how to generalise to solve the one above ?
Is this problem suitable for functional programming language ?
Any idea ? Cheers
_________________________________________________________________ It's fast, it's easy and it's free. Get MSN Messenger 7.0 today! http://messenger.msn.co.uk
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Here's mine, which is similar to Cale's, although done before I saw his: coins = reverse [1,5,10,25] change' 0 = [[]] change' amt = concat $ map subchange $ filter (amt >=) coins where -- recursively make change subchange c = map (\l -> c:l) $ filter (canon c) $ change' (amt - c) -- filter change lists to those in some canonical order -- this ensures uniqueness canon _ [] = True canon c (x:xs) = c <= x change amt num = filter (\l -> length l <= num) $ change' amt

Thanks for all your solutions It seems that recursion is the only way. i thought it is a variation of the "integer parition" problem so that can be solved linearly (by generating next solution in (anti)lexicographic order) i guess i have to learn Monads then, ^_^ Cheers
From: Kurt
Reply-To: Kurt To: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Coin changing algorithm Date: Wed, 13 Jul 2005 11:19:03 -0400 Here's mine, which is similar to Cale's, although done before I saw his:
coins = reverse [1,5,10,25]
change' 0 = [[]] change' amt = concat $ map subchange $ filter (amt >=) coins where -- recursively make change subchange c = map (\l -> c:l) $ filter (canon c) $ change' (amt - c)
-- filter change lists to those in some canonical order -- this ensures uniqueness canon _ [] = True canon c (x:xs) = c <= x
change amt num = filter (\l -> length l <= num) $ change' amt _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_________________________________________________________________ Winks & nudges are here - download MSN Messenger 7.0 today! http://messenger.msn.co.uk

On 7/13/05, Dinh Tien Tuan Anh
i guess i have to learn Monads then, ^_^
That's probably a good idea. But what about this problem made you think "monads"? Caching? The imperative solution you mentioned? -- regards, radu http://rgrig.blogspot.com/

it's because of the impreative approach. Seem more elegent than a functional approach. Where is the best place to find out about Monads. The book by Richard Bird is pretty confusing.
From: Radu Grigore
Reply-To: Radu Grigore To: Dinh Tien Tuan Anh CC: kelanslists@gmail.com, haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Coin changing algorithm Date: Wed, 13 Jul 2005 18:41:41 +0300 On 7/13/05, Dinh Tien Tuan Anh
wrote: i guess i have to learn Monads then, ^_^
That's probably a good idea. But what about this problem made you think "monads"? Caching? The imperative solution you mentioned?
-- regards, radu http://rgrig.blogspot.com/
_________________________________________________________________ It's fast, it's easy and it's free. Get MSN Messenger 7.0 today! http://messenger.msn.co.uk

heh, just noticed that the (amount > 0) test in the last guard is unnecessary (other cases added since then leave only that as a possibility) and it can be replaced by "otherwise", not that it makes too much of a difference:
import Monad import List
makeChange :: [Integer] -> Integer -> Integer -> [[Integer]] makeChange coins amount maxCoins | amount < 0 = [] | amount == 0 = [[]] | null coins = [] | amount `div` maximum coins > maxCoins = [] -- optimisation | otherwise = do x <- coins xs <- makeChange (filter (<= x) coins) (amount - x) (maxCoins - 1) guard (genericLength (x:xs) <= maxCoins) return (x:xs)
makeChange' :: Integer -> Integer -> [[Integer]] makeChange' amount maxCoins = makeChange coins amount maxCoins where coins = [200,100,50,20,10,5,2,1]
-- Cale
participants (9)
-
Cale Gibbard
-
ChrisK
-
Dinh Tien Tuan Anh
-
Ferenc Wagner
-
Henning Thielemann
-
Kurt
-
Mark Carroll
-
Radu Grigore
-
wenduan