RabbitFarm
2025-02-23
The Weekly Challenge 309 (Prolog Solutions)
The examples used here are from the weekly challenge problem statement and demonstrate the working solution.
Part 1: Min Gap
You are given an array of integers, @ints, increasing order. Write a script to return the element before which you find the smallest gap.
There are probably a few good approaches to this problem. Here we’ll use a DCG approach. Ultimately this problem is at its core is to process a list of integers, and processing a list is something a DCG is well suited to handle.
We will be passing the state of the minimal gap found through the list processing predicates. The plan is that every time we find a new smallest gap the element where we found it will be appended to the list, along with the size of the gap. At the end of processing the final element will contain where the smallest gap was found.
-
min_gap([]) --> [].
min_gap(Integers) --> {[_] = Integers}.
min_gap(Integers) -->
gap(G, Gap),
{[X,Y|T] = Integers, D is Y - X, var(G), G = D, append([], [G-Y], Gap)},
min_gap([Y|T]).
min_gap(Integers) -->
gap(G, Gap),
{[X,Y|T] = Integers, D is Y - X, last(G, GCurrent-_), D < GCurrent, append(G, [D-Y], Gap)},
min_gap([Y|T]).
min_gap(Integers) -->
gap(G, Gap),
{[X,Y|T] = Integers, D is Y - X, last(G, GCurrent-_), D >= GCurrent, Gap = G},
min_gap([Y|T]).
◇
-
Fragment referenced in 4.
Let’s give this DCG a simple interface. We’ll write a utility predicate that calls the DCG and sets the location of the smallest gap found.
-
min_gap(Integers, MinGapLocation):-
phrase(min_gap(Integers), [_], [Gaps]),
last(Gaps, _-MinGapLocation), !.
◇
-
Fragment referenced in 4.
The rest of the code just wraps this predicate into a file.
Sample Run
$ gprolog --consult-file prolog/ch-1.p | ?- min_gap([2, 8, 10, 11, 15], MinGapLocation). MinGapLocation = 11 (1 ms) yes | ?- min_gap([1, 5, 6, 7, 14], MinGapLocation). MinGapLocation = 6 yes | ?- min_gap([8, 20, 25, 28], MinGapLocation). MinGapLocation = 28 yes | ?-
Part 2: Min Diff
You are given an array of integers, @ints. Write a script to find the minimum difference between any two elements.
From Part 1 we know that if we sort the list we know we need to only check adjacent elements to find the minimum difference.
Much of the code is going to be the same. In fact there’s going to be less code since all we need to do is track the gap sizes and not the locations.
-
min_gap([]) --> [].
min_gap(Integers) --> {[_] = Integers}.
min_gap(Integers) -->
gap(G, Gap),
{[X,Y|T] = Integers, D is Y - X, var(G), G = D, append([], [G], Gap)},
min_gap([Y|T]).
min_gap(Integers) -->
gap(G, Gap),
{[X,Y|T] = Integers, D is Y - X, last(G, GCurrent), D < GCurrent, append(G, [D], Gap)},
min_gap([Y|T]).
min_gap(Integers) -->
gap(G, Gap),
{[X,Y|T] = Integers, D is Y - X, last(G, GCurrent), D >= GCurrent, Gap = G},
min_gap([Y|T]).
◇
-
Fragment referenced in 7.
As before let’s give this DCG a simple interface. We’ll write a utility predicate that calls the DCG and sets the smallest gap found.
-
min_gap(Integers, MinGap):-
msort(Integers, SortedIntegers),
phrase(min_gap(SortedIntegers), [_], [Gaps]),
last(Gaps, MinGap), !.
◇
-
Fragment referenced in 7.
Finally, let’s assemble our completed code into a single file.
Sample Run
$ gprolog prolog/ch-2.p | ?- min_gap([1, 5, 8, 9], MinGap). MinGap = 1 yes | ?- min_gap([9, 4, 1, 7], MinGap). MinGap = 2 yes | ?-
References
posted at: 20:01 by: Adam Russell | path: /prolog | permanent link to this entry