RabbitFarm

2022-03-06

The Weekly Challenge 154 (Prolog Solutions)

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

Part 1

Write a script to compute the first 10 distinct Padovan Primes.

Solution


:-initialization(main).

make_lists([], []).
make_lists([Word|Words], [List|Rest]):-
    atom_chars(Word, List),
    make_lists(Words, Rest).

missing_permutation(Word, Permutations, Missing):-
    atom_chars(Word, Chars),
    permutation(Chars, Permutation),
    \+ member(Permutation, Permutations),
    atom_chars(Missing, Permutation).

main:-
    make_lists(['PELR', 'PREL', 'PERL', 'PRLE', 'PLER', 'PLRE', 'EPRL', 'EPLR', 'ERPL',
                'ERLP', 'ELPR', 'ELRP', 'RPEL', 'RPLE', 'REPL', 'RELP', 'RLPE', 'RLEP',
                'LPER', 'LPRE', 'LEPR', 'LRPE', 'LREP'], Permutations),
    missing_permutation('PERL', Permutations, Missing),
    write(Missing), nl,
    halt.

Sample Run


$ gprolog --consult-file prolog/ch-1.p
LERP

Notes

This is a nice place where Prolog really shines compared to the Perl solution to the same problem. That approach requires a good deal of care to properly generalize. The Prolog solution is completely general without any extra work! Here we need only split the starting word into characters and then backtrack through any possible missing permutations with permutation/2 and member/2. Elegant!

Part 2

Write a script to compute the first 10 distinct Padovan Primes.

Solution


padovan_primes(Size, Primes, PrimesAccum, A, B, C) --> {D is B + A, fd_not_prime(D)}, [A], padovan_primes(Size, Primes, PrimesAccum, B, C, D).
padovan_primes(Size, Primes, PrimesAccum, A, B, C) --> {D is B + A, fd_prime(D), append(PrimesAccum, [D], NewPrimesAccum), length(NewPrimesAccum, L), L < Size}, [A], padovan_primes(Size, Primes, NewPrimesAccum, B, C, D).
padovan_primes(Size, Primes, PrimesAccum, A, B, _) --> {D is B + A, fd_prime(D), append(PrimesAccum, [D], NewPrimesAccum), length(NewPrimesAccum, L), L >= Size, Primes = NewPrimesAccum}, [D].

n_padovan_primes(N, Primes):-
    succ(N, X),
    phrase(padovan_primes(X, PadovanPrimes, [], 1, 1, 1), _),
    [_|Primes] = PadovanPrimes.

Sample Run


$ gprolog --consult-file prolog/ch-2.p 
| ?- n_padovan_primes(7, Primes).

Primes = [2,3,5,7,37,151,3329] ? 

(113 ms) yes
| ?-

Notes

If you watch any of the videos on The Power of Prolog YouTube channel you'll learn from Markus Triska that a DCG is the preferable way to handle this sort of problem. Not just because DCGs are a convenient way to process a list in Prolog, but because they can be used to both generate and test solutions. Excellent advice! This code above shows this for a somewhat complicated problem. We must generate the sequence and also determine which of the sequence terms are prime. Primality testing is performed by GNU Prolog's fd_prime/1 and fd_not_prime/1. As the primes are found they are added, along with the most recently computed three sequence terms, as extra arguments.

This solution is very similar to a previous bit of code for Fibonacci Strings.

References

Challenge 154

Padovan Sequence

The Power of Prolog: YouTube Channel

The Power of Prolog

posted at: 19:25 by: Adam Russell | path: /prolog | permanent link to this entry