RabbitFarm

2025-03-16

The Weekly Challenge 312 (Prolog Solutions)

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

Part 1: Minimum Time

You are given a typewriter with lowercase english letters a to z arranged in a circle. Typing a character takes 1 sec. You can move pointer one character clockwise or anti-clockwise. The pointer initially points at a. Write a script to return minimum time it takes to print the given string.

All the logic for computing the shortest move us contained in a single predicate.

compute minumum number of moves to get to the next letter 1 ⟩≡


compute_moves(Current, Next, Moves):-
X is Current - 96,
Y is Next - 96,
XH is X + 13,
YH is Y + 13,
((Y >= XH, Moves is X + 26 - Y);
(Y >= X, Y =< XH, Moves is Y - X);
(X >= YH, Moves is Y + 26 - X);
(X >= Y, X =< YH, Moves is X - Y)).

Fragment referenced in 3.

We’ll use a DCG to process the list of letters (we’re using ASCII codes).

process letters 2 ⟩≡


minimum_time([Current, Next|Letters]) --> [Time], {
compute_moves(Current, Next, Moves),
succ(Moves, Time)}, minimum_time([Next|Letters]).
minimum_time([_]) --> [].

Fragment referenced in 3.

Finally, let’s combine the previous predicates into a file along with a predicate minimum_time/2 that ties everything together.

"ch-1.p" 3


compute minumum number of moves to get to the next letter 1
process letters 2
minimum_time(S, MinimumTime):-
append([97], S, S0),
phrase(minimum_time(S0), Times),
sum_list(Times, MinimumTime), !.

Sample Run
$ gprolog --consult-file prolog/ch-1.p 
| ?- minimum_time("abc", MinimumTime). 
 
MinimumTime = 5 
 
yes 
| ?- minimum_time("bza", MinimumTime). 
 
MinimumTime = 7 
 
yes 
| ?- minimum_time("zjpc", MinimumTime). 
 
MinimumTime = 34 
 
yes 
| ?-
    

Part 2: Balls and Boxes

There are $n balls of mixed colors: red, blue or green. They are all distributed in 10 boxes labelled 0-9. You are given a string describing the location of balls. Write a script to find the number of boxes containing all three colors. Return 0 if none found.

We’ll use a DCG here in Part 2, althought it’ll be just a little bit more intricate.

First off, we’ll be passing the state around via some helper predicates. At the end of processing we’ll have a set of pairs that hold the contents of each box.

state of the content of the boxes 4 ⟩≡


boxes(Boxes), [Boxes] --> [Boxes].
boxes(Box, Boxes), [Boxes] --> [Box].

Fragment referenced in 7.

Now the DCG. For each record given we’ll process each Ball/Box pair.

process the record of box contents as a list 5 ⟩≡


box_record([]) --> [].
box_record(Record) --> boxes(B, Boxes), {[Color, Box|T] = Record,
var(B), B = Box-[Color], append([], [B], Boxes)},
box_record(T).
box_record(Record) --> boxes(B, Boxes), {[Color, Box|T] = Record,
nonvar(B), member(Box-Colors, B), delete(B, Box-Colors, B0),
append([Color], Colors, Colors0), append([Box-Colors0], B0, Boxes)},
box_record(T).
box_record(Record) --> boxes(B, Boxes), {[Color, Box|T] = Record,
nonvar(B), \+ member(Box-_, B), append([Box-[Color]], B, Boxes)},
box_record(T).

Fragment referenced in 7.

helper predicate for checking if a box has all three colors 6 ⟩≡


full_box(_-Colors, Full):-
sort(Colors, ColorsSorted),
length(ColorsSorted, NumberColors),
((NumberColors == 3, Full = true);
(Full = false)).

Fragment referenced in 7.

Finally, let’s assemble our completed code into a single file. We’ll also add a predicate to co-orindate calling the DCG and processing the final result.

"ch-2.p" 7


state of the content of the boxes 4
process the record of box contents as a list 5
helper predicate for checking if a box has all three colors 6
full_boxes(BallsBoxes, CountFullBoxes):-
phrase(box_record(BallsBoxes), [_], [Boxes]),
maplist(full_box, Boxes, Full),
delete(Full, false, FullBoxes),
length(FullBoxes, CountFullBoxes), !.

Sample Run
$ gprolog --consult-file prolog/ch-2.p 
| ?- full_boxes("G0B1R2R0B0", FullBoxes). 
 
FullBoxes = 1 
 
yes 
| ?- full_boxes("G1R3R6B3G6B1B6R1G3", FullBoxes). 
 
FullBoxes = 3 
 
yes 
| ?- full_boxes("B3B2G1B3", FullBoxes). 
 
FullBoxes = 0 
 
yes 
| ?-
    

References

The Weekly Challenge 312
Generated Code

posted at: 15:35 by: Adam Russell | path: /prolog | permanent link to this entry