home *** CD-ROM | disk | FTP | other *** search
/ NetNews Usenet Archive 1993 #1 / NN_1993_1.iso / spool / comp / lang / prolog / 2319 < prev    next >
Encoding:
Internet Message Format  |  1993-01-05  |  4.1 KB

  1. Path: sparky!uunet!pipex!bnr.co.uk!uknet!edcastle!aiai!ken
  2. From: ken@aiai.ed.ac.uk (Ken Johnson)
  3. Newsgroups: comp.lang.prolog
  4. Subject: Re: Making up sums of money from coins
  5. Message-ID: <8090@skye.ed.ac.uk>
  6. Date: 5 Jan 93 18:31:12 GMT
  7. References: <8088@skye.ed.ac.uk>
  8. Followup-To: comp.lang.prolog
  9. Organization: William's Wonderful Wonky Widget Warehouse
  10. Lines: 105
  11.  
  12.  
  13. Well, I thought this was a dry-as-dust topic, but correspondence by
  14. E-mail has already revealed two interesting(?) facets.  Or maybe it
  15. revealed how bored I am. 
  16.  
  17. Firstly: Here is a brute-force-and-ignorance way of minimising the
  18. number of coins in old British money.  It works by applying the usual
  19. largest-fit algorithm, and then searches by binary chop to see whether
  20. it can find a combination of fewer coins.  There is an assumption that
  21. if (say) the largest-fit algorithm requires 8 coins and in fact at least
  22. 4 coins are required, then solutions requiring exactly 5, 6 and 7 coins
  23. also exist.  If this assumption is false, and it probably is, binary
  24. chop won't work, and you have to try every number between
  25. (Sum/Value_of_largest_coin) and (Number_required_by_largest_fit). 
  26.  
  27. Secondly: After that, I have written the largest-fit solution to the
  28. problem as a DCG!
  29.  
  30. (A) Fewest Coins Algorithm:
  31.  
  32.           fewest_coins(Sum,Coins) :-
  33.               Sum > 0,
  34.               make(Sum,Sum,_,Max_needed),
  35.               chop(0,Max_needed,Limit,make(Sum,Limit,Coins),Fewest),
  36.               make(Sum,Fewest,Coins).
  37.  
  38.           make(Sum,Max_coins,Coins) :-
  39.               make(Sum,Max_coins,0,Coins,_).
  40.           
  41.           make(Sum,Max_coins,Coins,N_used) :-
  42.               make(Sum,Max_coins,0,Coins,N_used).
  43.           
  44.           make(0,_,Used,[],Used).
  45.           
  46.           make(Sum,Limit,Used,[Name|Rest],U_out) :-
  47.               Used < Limit,
  48.               coin(Name,Value),
  49.               Value =< Sum,
  50.               Residue is Sum - Value,
  51.               New_used is Used + 1,
  52.               make(Residue,Limit,New_used,Rest,U_out).
  53.           
  54.           
  55.           % Coins; must be in order of decreasing value.
  56.           
  57.           coin('ten shilling note',120).
  58.           coin('half-crown',30).
  59.           coin(florin,24).
  60.           coin(shilling,12).
  61.           coin(sixpence,6).
  62.           coin('threepenny bit',3).
  63.           coin(penny,1).
  64.           
  65.           % Search for minimum by binary chop.  This is a utility you ought to
  66.           % have in your filofax or somewhere. 
  67.           
  68.           chop(Highest_fail,Lowest_success,_,_,Lowest_success) :-
  69.               Lowest_success - Highest_fail =< 1,
  70.               !.
  71.           
  72.           chop(Highest_fail,Lowest_success,Var,Term,Result) :-
  73.               Try is (Lowest_success + Highest_fail) // 2,
  74.               \+ \+ (                % Avoid instantiating Var
  75.                   Var = Try,
  76.                   Term
  77.                     ),
  78.               !,
  79.               chop(Highest_fail,Try,Var,Term,Result).
  80.           
  81.           chop(Highest_fail,Lowest_success,Var,Term,Result) :-
  82.               Try is (Lowest_success + Highest_fail) // 2,
  83.               chop(Try,Lowest_success,Var,Term,Result).
  84.           
  85. Example run of (A)
  86.  
  87.            ?- fewest_coins(49,X).
  88.  
  89.               X=[florin,florin,penny]
  90.  
  91. (B) The problem expressed as a DCG
  92.  
  93.           sum(S) --> coin(V), {V =< S, !, T is S-V}, sum(T).
  94.           sum(0) --> [].
  95.           
  96.           coin(120) --> ['ten shilling note'].
  97.           coin(30)  --> ['half-crown'].
  98.           coin(24)  --> [florin].
  99.           coin(12)  --> [shilling].
  100.           coin(6)   --> [sixpence].
  101.           coin(3)   --> ['threepenny bit'].
  102.           coin(1)   --> [penny].
  103.  
  104. Example run of (B)
  105.  
  106.           ?- phrase(sum(49),X).
  107.           
  108.           X=[half-crown,shilling,sixpence,penny]
  109.  
  110. (this being of course correct, but less than optimal). 
  111.  
  112. -- 
  113. Son, all the pretty, intelligent,      || Ken Johnson                           healthy young women are taken.         || A I Applications Institute
  114. It's a basic rule of the universe,     || 80 South Bridge                       and if you don't like it,              || Edinburgh,  Scotland   EH1 1HN
  115. go somewhere else.                     || Phone 031-650 2756   Fax 031-650 6513
  116.                -- my dad  1906-1992    || E-mail ken@aiai.ed.ac.uk
  117.