RabbitFarm

2025-06-06

The Weekly Challenge 323 (Prolog Solutions)

The examples used here are from the weekly challenge problem statement and demonstrate the working solution.

Part 1: Increment Decrement

You are given a list of operations. Write a script to return the final value after performing the given operations in order. The initial value is always 0.

Our solution will be contained in a single file that has the following structure.

"ch-1.p" 1


update input variables 4
state of the variables 2
process input 3
show final state of the variables 5
increment decrement 6

We’ll use a DCG approach to process the input and maintain the state of the variables.

First, let’s have some predicates for maintaining the state of the variables as the DCG processes the input.

state of the variables 2 ⟩≡


variables(VariableState), [VariableState] --> [VariableState].
variables(V, VariableState), [VariableState] --> [V].

Fragment referenced in 1.

Now we need to process the input, which we’ll treat as lists of character codes.

process input 3 ⟩≡


process(Input) --> variables(V, VariableState),
{Input = [Code1, Code2, Code3 | Codes],
Code1 == 43, Code2 == 43, Code3 >= 97,
Code3 =< 122,
increment_variable(Code3, V, VariableState)},
process(Codes).
process(Input) --> variables(V, VariableState),
{Input = [Code1, Code2, Code3 | Codes],
Code2 == 43, Code3 == 43, Code1 >= 97,
Code1 =< 122,
increment_variable(Code1, V, VariableState)},
process(Codes).
process(Input) --> variables(V, VariableState),
{Input = [Code1, Code2, Code3 | Codes],
Code1 == 45, Code2 == 45, Code3 >= 97,
Code3 =< 122,
decrement_variable(Code3, V, VariableState)},
process(Codes).
process(Input) --> variables(V, VariableState),
{Input = [Code1, Code2, Code3 | Codes],
Code2 == 45, Code3 == 45, Code1 >= 97,
Code1 =< 122,
decrement_variable(Code1, V, VariableState)},
process(Codes).
process(Input) --> variables(V, VariableState),
{Input = [Code | Codes],
Code >= 97, Code =< 122,
declare_variable(Code, V, VariableState)},
process(Codes).
process(Input) --> {Input = [Code | Codes],
Code == 32},
process(Codes).
process([]) --> [].

Fragment referenced in 1.

We’ll define some utility predicates for updating the state of the variables in our DCG input.

update input variables 4 ⟩≡


increment_variable(X, U, V):-
member(X-I, U),
delete(U, X-I, U1),
I1 is I + 1,
append([X-I1], U1, V).
increment_variable(X, U, V):-
\+ member(X-_, U),
append([X-1], U, V).
decrement_variable(X, U, V):-
member(X-I, U),
delete(U, X-I, U1),
I1 is I - 1,
append([X-I1], U1, V).
decrement_variable(X, U, V):-
\+ member(X-_, U),
append([X-(-1)], U, V).
declare_variable(X, U, V):-
delete(U, X-_, U1),
append([X-0], U1, V).

Fragment referenced in 1.

One more small utility predicate. This one is for displaying the final results. It’s intended to be called from maplist/2.

show final state of the variables 5 ⟩≡


show_variables(X-I):-
atom_codes(A, [X]),
write(A),
write(’:␣’),
write(I), nl.

Fragment referenced in 1.

Finally, let’s wrap the calls to the DCG in a small predicate using phrase/3.

increment decrement 6 ⟩≡


increment_decrement(Input):-
phrase(process(Input), [[]], [Output]), !,
maplist(show_variables, Output).

Fragment referenced in 1.

Sample Run
$ gprolog --consult-file prolog/ch-1.p 
| ?- increment_decrement("--xx++x++"). 
x: 1 
 
yes 
| ?- increment_decrement("x++++xx++"). 
x: 3 
 
(1 ms) yes 
| ?- increment_decrement("x++++x--xx--"). 
x: 0 
 
yes 
| ?- increment_decrement("abca++b++c++++a++b++c--a--b--ca--b--c--a++++bc++"). 
c: 1 
b: 1 
a: 1 
 
yes 
| ?-
    

Part 2: Tax Amount

You are given an income amount and tax brackets. Write a script to calculate the total tax amount.

While a DCG approach is also certainly possible for this second part we’ll go with a more plain recursive solution.

"ch-2.p" 7


compute taxes 8

The code is simple enough that it is pretty explainable in one single code section.

compute taxes 8 ⟩≡


compute_taxes(Income, TaxBrackets, Tax):-
compute_taxes(Income, TaxBrackets, 0, 0, Tax).
compute_taxes(0, _, 0, 0, 0).
compute_taxes(Income, [[Limit, Rate]|TaxBrackets], Taxable, Taxed, Tax):-
Limit =< Income,
Taxable1 is Limit - Taxable,
Taxed1 is Taxed + Taxable1,
compute_taxes(Income, TaxBrackets, Taxable1, Taxed1, Tax1),
Tax is Tax1 + (Taxable1 * (Rate/100)).
compute_taxes(Income, [[Limit, Rate]|_], _, Taxed, Tax):-
Limit > Income,
Tax is ((Income - Taxed) * (Rate/100)).

Fragment referenced in 7.

Sample Run
$ gprolog --consult-file prolog/ch-2.p 
| ?- compute_taxes(10, [[3, 50], [7, 10], [12,25]], Tax), format("$~2f", [Tax]). 
$2.65 
 
Tax = 2.6499999999999999 ? 
 
yes 
| ?- compute_taxes(2, [[1, 0], [4, 25], [5,50]], Tax), format("$~2f", [Tax]). 
$0.25 
 
Tax = 0.25 ? 
 
yes 
| ?- compute_taxes(0, [[2, 50]], Tax), format("$~2f", [Tax]). 
$0.00 
 
Tax = 0 ? 
 
yes 
| ?-
    

References

The Weekly Challenge 323
Generated Code

posted at: 17:05 by: Adam Russell | path: /prolog | permanent link to this entry