home *** CD-ROM | disk | FTP | other *** search
- Path: sparky!uunet!pipex!bnr.co.uk!uknet!edcastle!aiai!ken
- From: ken@aiai.ed.ac.uk (Ken Johnson)
- Newsgroups: comp.lang.prolog
- Subject: Re: Making up sums of money from coins
- Message-ID: <8090@skye.ed.ac.uk>
- Date: 5 Jan 93 18:31:12 GMT
- References: <8088@skye.ed.ac.uk>
- Followup-To: comp.lang.prolog
- Organization: William's Wonderful Wonky Widget Warehouse
- Lines: 105
-
-
- Well, I thought this was a dry-as-dust topic, but correspondence by
- E-mail has already revealed two interesting(?) facets. Or maybe it
- revealed how bored I am.
-
- Firstly: Here is a brute-force-and-ignorance way of minimising the
- number of coins in old British money. It works by applying the usual
- largest-fit algorithm, and then searches by binary chop to see whether
- it can find a combination of fewer coins. There is an assumption that
- if (say) the largest-fit algorithm requires 8 coins and in fact at least
- 4 coins are required, then solutions requiring exactly 5, 6 and 7 coins
- also exist. If this assumption is false, and it probably is, binary
- chop won't work, and you have to try every number between
- (Sum/Value_of_largest_coin) and (Number_required_by_largest_fit).
-
- Secondly: After that, I have written the largest-fit solution to the
- problem as a DCG!
-
- (A) Fewest Coins Algorithm:
-
- fewest_coins(Sum,Coins) :-
- Sum > 0,
- make(Sum,Sum,_,Max_needed),
- chop(0,Max_needed,Limit,make(Sum,Limit,Coins),Fewest),
- make(Sum,Fewest,Coins).
-
- make(Sum,Max_coins,Coins) :-
- make(Sum,Max_coins,0,Coins,_).
-
- make(Sum,Max_coins,Coins,N_used) :-
- make(Sum,Max_coins,0,Coins,N_used).
-
- make(0,_,Used,[],Used).
-
- make(Sum,Limit,Used,[Name|Rest],U_out) :-
- Used < Limit,
- coin(Name,Value),
- Value =< Sum,
- Residue is Sum - Value,
- New_used is Used + 1,
- make(Residue,Limit,New_used,Rest,U_out).
-
-
- % Coins; must be in order of decreasing value.
-
- coin('ten shilling note',120).
- coin('half-crown',30).
- coin(florin,24).
- coin(shilling,12).
- coin(sixpence,6).
- coin('threepenny bit',3).
- coin(penny,1).
-
- % Search for minimum by binary chop. This is a utility you ought to
- % have in your filofax or somewhere.
-
- chop(Highest_fail,Lowest_success,_,_,Lowest_success) :-
- Lowest_success - Highest_fail =< 1,
- !.
-
- chop(Highest_fail,Lowest_success,Var,Term,Result) :-
- Try is (Lowest_success + Highest_fail) // 2,
- \+ \+ ( % Avoid instantiating Var
- Var = Try,
- Term
- ),
- !,
- chop(Highest_fail,Try,Var,Term,Result).
-
- chop(Highest_fail,Lowest_success,Var,Term,Result) :-
- Try is (Lowest_success + Highest_fail) // 2,
- chop(Try,Lowest_success,Var,Term,Result).
-
- Example run of (A)
-
- ?- fewest_coins(49,X).
-
- X=[florin,florin,penny]
-
- (B) The problem expressed as a DCG
-
- sum(S) --> coin(V), {V =< S, !, T is S-V}, sum(T).
- 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].
-
- Example run of (B)
-
- ?- phrase(sum(49),X).
-
- X=[half-crown,shilling,sixpence,penny]
-
- (this being of course correct, but less than optimal).
-
- --
- Son, all the pretty, intelligent, || Ken Johnson healthy young women are taken. || A I Applications Institute
- It's a basic rule of the universe, || 80 South Bridge and if you don't like it, || Edinburgh, Scotland EH1 1HN
- go somewhere else. || Phone 031-650 2756 Fax 031-650 6513
- -- my dad 1906-1992 || E-mail ken@aiai.ed.ac.uk
-