RabbitFarm

2025-05-26

The Weekly Challenge 322 (Prolog Solutions)

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

Part 1:String Format

You are given a string and a positive integer. Write a script to format the string, removing any dashes, in groups of size given by the integer. The first group can be smaller than the integer but should have at least one character. Groups should be separated by dashes.

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

"ch-1.p" 1


state of the formatted string 2
process string 3
string format 4

We’ll use a DCG approach to process the string and maintain the result.

First, let’s have some predicates for maintaining the state of a character list as the DCG processes the string.

state of the formatted string 2 ⟩≡


format_(Format), [Format] --> [Format].
format_(F, Format), [Format] --> [F].

Fragment referenced in 1.

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

process string 3 ⟩≡


process(String, I, J) --> {String = [Code | Codes],
Code == 45},
process(Codes, I, J).
process(String, I, J) --> format_(F, Format),
{String = [Code | Codes],
\+ Code == 45,
succ(J, I),
char_code(C, Code),
length(Codes, L),
((L > 0, Format = [’-’, C|F]);
(Format = [C|F]))},
process(Codes, I, 0).
process(String, I, J) --> format_(F, Format),
{String = [Code | Codes],
\+ Code == 45,
succ(J, J1),
char_code(C, Code),
Format = [C|F]},
process(Codes, I, J1).
process([], _, _) --> [].

Fragment referenced in 1.

Finally, let’s wrap the calls to the DCG in a small predicate using phrase/3. We’re going to work from right to left so we’ll use reverse/2 to input into our DCG.

string format 4 ⟩≡


string_format(String, I, FormattedString):-
reverse(String, R),
phrase(process(R, I, 0), [[]], [F]), !,
atom_chars(FormattedString, F).

Fragment referenced in 1.

Sample Run
$ gprolog --consult-file prolog/ch-1.p 
| ?- string_format("ABC-D-E-F", 3, F). 
 
F = ’ABC-DEF’ 
 
yes 
| ?- string_format("A-BC-D-E", 2, F). 
 
F = ’A-BC-DE’ 
 
yes 
| ?- string_format("-A-B-CD-E", 4, F). 
 
F = ’A-BCDE’ 
 
yes 
| ?-
    

Part 2: Rank Array

You are given an array of integers. Write a script to return an array of the ranks of each element: the lowest value has rank 1, next lowest rank 2, etc. If two elements are the same then they share the same rank.

We’ll sort/2 the list of integers and then use the sroted list to look up the rank using nth/3. Remember, sort/2 removes duplicates! If it did not this approach would require extra work to first get the unique values.

"ch-2.p" 5


rank lookup  6
rank list 7

This is a predicate we’ll call via maplist.

rank lookup  6 ⟩≡


rank(SortedList, X, Rank):-
nth(Rank, SortedList, X).

Fragment referenced in 5.

We’ll define a predicate to do an initial sort and call rank/3.

rank list 7 ⟩≡


rank_list(L, Ranks):-
sort(L, Sorted),
maplist(rank(Sorted), L, Ranks).

Fragment referenced in 5.

Sample Run
$ gprolog --consult-file prolog/ch-2.p 
| ?- rank_list([55, 22, 44, 33], Ranks). 
 
Ranks = [4,1,3,2] ? 
 
yes 
| ?- rank_list([10, 10, 10], Ranks). 
 
Ranks = [1,1,1] ? 
 
yes 
| ?- rank_list([5, 1, 1, 4, 3], Ranks). 
 
Ranks = [4,1,1,3,2] ? 
 
yes 
| ?-
    

References

The Weekly Challenge 322
Generated Code

posted at: 00:31 by: Adam Russell | path: /prolog | permanent link to this entry