home *** CD-ROM | disk | FTP | other *** search
- Path: sparky!uunet!mcsun!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: <8134@skye.ed.ac.uk>
- Date: 8 Jan 93 17:32:49 GMT
- References: <8088@skye.ed.ac.uk>
- Followup-To: comp.lang.prolog
- Organization: William's Wonderful Wonky Widget Warehouse
- Lines: 64
-
-
- The following code works, but I have not a clue how to generalise it.
- At least, I have not chanced upon a case where it does not give the best
- answer. The reason for the op/3 call will become clear in a minute,
- although those over thirty will recognise it on sight:
-
- :- op(500, xf, '/-').
-
- make(A/-,C) :-
- Sum is 12 * A,
- make(Sum,C).
-
- make(A/B,C) :-
- Sum is A * 12 + B,
- make(Sum,C).
-
- make(0,[]).
-
- make(Sum,[Name|Rest]) :-
- Sixpences is Sum//6, % If the number of sixpences
- coin(Name,Value), % in the sum is an exact
- Value =< Sum, % multiple of 4, then do not
- \+ ( 0 is Sixpences mod 4, % allocate a half crown.
- Value is 30 % No clue how to generalise
- ), % this to other currencies.
- Residue is Sum - Value, % The LCM of 4 and 5 is 20 so
- make(Residue,Rest). % 10/- is dispensed as a
- % ten shilling note, not as
- % five florins (wrong)
- % 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).
-
- % Sample Run
-
- This program understands the traditional way of writing `four shillings'
- as 4/- and four shillings and elevenpence as 4/11.
-
- ?- make(4/-,X).
- X=[florin,florin]
-
- ?- make(4/6,X).
- X=[half-crown,florin]
-
- ?- make(5/-,X).
- X=[half-crown,half-crown]
-
- ?- make(5/11,X).
- X=[half-crown,half-crown,sixpence,threepenny bit,penny,penny]
-
-
- Ken Johnson
-
- --
- Son, all the pretty, intelligent, healthy # Ken Johnson, AIAI,
- young women are taken. It's a basic rule of # 80 South Bridge, Edinburgh
- the universe, and if you don't like it, go # Tel 031-650 2756
- somewhere else. -- my dad 1906-1992 # Fax 031-650 6513
-