RabbitFarm
2025-07-09
The Weekly Challenge 328 (Prolog Solutions)
The examples used here are from the weekly challenge problem statement and demonstrate the working solution.
Part 1: Replace all ?
You are given a string containing only lower case English letters and ?. Write a script to replace all ? in the given string so that the string doesn’t contain consecutive repeating characters.
Our solution is short and will be contained in a single file that has the following structure.
Let’s use a DCG! First we’ll define a couple of helper rules to track the state of the replacement as the string gets processed.
-
replacement(Replacement), [Replacement] --> [Replacement].
replacement(R, Replacement), [Replacement] --> [R].
◇
-
Fragment referenced in 1.
Next let’s have the DCG rules themselves. This looks a little more complex then it could be just because I handle certain corner cases as separate rules. Basically all we’re doing is looking at the current character code of the string to see if it’s a question mark (63) and if it is then check the previous character and the next character and rely on backtracking to find a suitable random letter. The corner cases are for when we have no previous character and if we just have one character remaining to process. We also consider the case when we have a character other than ?.
-
replace(Input) --> replacement(R, Replacement),
{\+ R == [],
Input = [C, CNext|T],
C == 63,
random(97, 123, C0),
last(R, CPrevious),
\+ C0 == CPrevious,
\+ C0 == CNext,
append(R, [C0], Replacement)
},
replace([CNext|T]).
replace(Input) --> replacement(R, Replacement),
{R == [],
Input = [C, CNext|T],
C == 63,
random(97, 123, C0),
\+ C0 == CNext,
append(R, [C0], Replacement)
},
replace([CNext|T]).
replace(Input) --> replacement(R, Replacement),
{Input = [C|T],
\+ C == 63,
append(R, [C], Replacement)
},
replace(T).
replace(Input) --> replacement(R, Replacement),
{Input = [C|T],
C == 63,
random(97, 123, C0),
last(R, CPrevious),
\+ C0 == CPrevious,
append(R, [C0], Replacement)
},
replace(T).
replace([]) --> [].
◇
-
Fragment referenced in 1.
Finally we’ll have a small predicate for calling the DCG using phrase/3 and formatting the result.
-
replace_qs(S, Replaced):-
phrase(replace(S), [[]], [ReplacedCodes]),
atom_codes(Replaced, ReplacedCodes).
◇
-
Fragment referenced in 1.
Sample Run
$ gprolog --consult-file prolog/ch-1.p | ?- replace_qs("a?z", Replaced). Replaced = adz ? (1 ms) yes | ?- replace_qs("pe?k", Replaced). Replaced = petk ? yes | ?- replace_qs("gra?te", Replaced). Replaced = gralte ? yes | ?- replace_qs("abcdefg", Replaced). Replaced = abcdefg ? yes | ?-
Part 2: Good String
You are given a string made up of lower and upper case English letters only. Write a script to return the good string of the given string. A string is called good string if it doesn’t have two adjacent same characters, one in upper case and other is lower case.
Let’s use DCGs again! This will proceed in a way very similar to Part 1.
Some helper rules to track the state of the deletions of the ”bad pairs“. The state will be maintained as modifications of the original string. This may seem a little unusual at first, we aren’t iterating over the string, rather we are iterating over all possible bad pairs. Maybe this use of a DCG is a little clunky, but why let that stop us!
(I say this is “clunky” because here we’re mainly using DCG notation simply as an alternative to ordinary recursion. There’s nothing being parsed per se and there is nothing especially interesting about the list being processed.)
-
deletion(Deletion), [Deletion] --> [Deletion].
deletion(D, Deletion), [Deletion] --> [D].
◇
-
Fragment referenced in 5.
-
bad_pair([], _):- false.
bad_pair(S, P):-
member(X, S),
member(Y, S),
\+ X == Y,
nth(I, S, X),
nth(J, S, Y),
succ(I, J),
(X is Y + 32; X is Y - 32), P = [I, J], !.
◇
-
Fragment referenced in 5.
The main DCG rules.
-
make_good(S) --> deletion(D, Deletion),
{D == [], \+ S == [], Deletion = S},
make_good(S).
make_good(S) --> deletion(D, Deletion),
{\+ D == [],
bad_pair(S, P),
[I, _] = P,
I > 1,
prefix(Prefix, S),
length(Prefix, I0),
I0 is I - 1,
append(Prefix, [_, _|Rest], S),
append(Prefix, Rest, Deletion)
},
make_good(Deletion).
make_good(S) --> deletion(D, Deletion),
{\+ D == [],
bad_pair(S, P),
[I, _] = P,
I == 1,
append([_, _], Deletion, S)
},
make_good(Deletion).
make_good(S) --> deletion(_, Deletion),
{\+ bad_pair(S, _),
Deletion = S}.
make_good([]) --> [].
◇
-
Fragment referenced in 5.
Finally we’ll have a small predicate for calling the DCG using phrase/3.
-
make_good_string(S, Good):-
phrase(make_good(S), [[]], [GoodCodes]),
atom_codes(Good, GoodCodes), !.
◇
-
Fragment referenced in 5.
Sample Run
$ gprolog --consult-file prolog/ch-2.p | ?- make_good_string("WeEeekly", Good). Good = ’Weekly’ (1 ms) yes | ?- make_good_string("abBAdD", Good). Good = ’’ yes | ?- make_good_string("abc", Good). Good = abc yes | ?-
References
posted at: 19:32 by: Adam Russell | path: /prolog | permanent link to this entry