home *** CD-ROM | disk | FTP | other *** search
- Newsgroups: comp.lang.prolog
- Path: sparky!uunet!infonode!ingr!capalo!quintus!quintus!ludemann
- From: ludemann@quintus.com (Peter Ludemann)
- Subject: Re: British coinage problem
- Message-ID: <1993Jan8.220355.3496@quintus.com>
- Keywords: iterative deepening, DCG
- Sender: news@quintus.com (USENET news account)
- Nntp-Posting-Host: ebisu
- Organization: Quintus Corporation, Palo Alto, CA
- References: <1993Jan7.141322.22240@ecrc.de> <8118@skye.ed.ac.uk>
- Date: Fri, 8 Jan 1993 22:03:55 GMT
- Lines: 45
-
- /* Problem: to find the smallest number of old British coins
- that sum up to some amount.
-
- Technique: iterative deepening, with a limit from the first
- solution found. (If the limit isn't provided, there would
- be infinite backtracking if you tried to use this predicate
- to find all solutions.) The iterative deepening calls sum//1
- with the lists [_], [_,_], [_,_,_] up to the limit length.
- */
-
- shortest_sum(Sum, Coins) :-
- sum(Sum, Coins1), !, /* we want one solution for a bound */
- length(Coins1, MaxLength),
- shortest_sum(Sum, Coins, 1, MaxLength),
- !. /* and no need to compute any more solutions */
-
- shortest_sum(Sum, Coins, Length, MaxLength) :-
- Length =< MaxLength,
- shortest_sum2(Sum, Coins, Length, MaxLength).
-
- shortest_sum2(Sum, Coins, Length, _) :-
- length(Coins, Length), /* create Coins list of given Length */
- sum(Sum, Coins).
- shortest_sum2(Sum, Coins, Length, MaxLength) :-
- Length2 is Length + 1,
- shortest_sum(Sum, Coins, Length2, MaxLength).
-
- /* Here is John Dowding's DCG method for generating lists of
- possible solutions (I've removed one cut from his code): */
-
- sum(Sum, Coins) :- phrase(sum(Sum), Coins).
-
- sum(Sum) --> coin(V), {V =< Sum, Rest is Sum-V}, sum(Rest).
- sum(0) --> [].
-
- coin(120) --> ['ten shilling note'].
- coin(30) --> ['half-crown'].
- coin(24) --> [florin].
- coin(12) --> [shilling].
- coin(6) --> [sixpence].
- coin(3) --> ['threepenny bit'].
- coin(1) --> [penny].
-
- - Peter Ludemann
-
-