RabbitFarm

2022-06-12

The Weekly Challenge 168 (Prolog Solutions)

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

Part 1

Calculate the first 13 Perrin Primes.

Solution


perrin_primes(A, B, C) --> {D is B + A, fd_not_prime(D)}, 
                           perrin_primes(B, C, D).
perrin_primes(A, B, C) --> {D is B + A, fd_prime(D), D \== C}, 
                           [D], perrin_primes(B, C, D).
perrin_primes(A, B, C) --> {D is B + A, fd_prime(D), D == C}, 
                           [], perrin_primes(B, C, D).                           
perrin_primes(_, _, _) --> [], !.

n_perrin_primes(N, PerrinPrimes):-
    length(PerrinPrimes, N), 
    phrase(perrin_primes(3, 0, 2), PerrinPrimes). 

Sample Run


$ gprolog --consult-file prolog/ch-1.p 
| ?- n_perrin_primes(13, PerrinPrimes).

PerrinPrimes = [3,2,5,7,17,29,277,367,853,14197,43721,1442968193,792606555396977] ? 

Notes

This is a pretty cut and dry use of a DCG to generate this interesting mathematical sequence. A couple of things that stand out are (1) the condition that D \== C which is to remove the duplicate 5 which occurs naturally at the beginning of the sequence. Afterwards all of the terms strictly increase. Also, (2) although the first two terms are indeed 3, 2 it is a convention to sort these and present them as 2, 3 although I did not happen to do so here.

Part 2

You are given an integer greater than 1. Write a script to find the home prime of the given number.

Solution


prime_factors(N, L):- 
    N > 0,  
    prime_factors(N, L, 2).
prime_factors(1, [], _):- 
    !.
prime_factors(N, [F|L], F):-                     
    R is N // F, 
    N =:= R * F, 
    !, 
    prime_factors(R, L, F).
prime_factors(N, L, F):-
    next_factor(N, F, NF), 
    prime_factors(N, L, NF).
next_factor(_, 2, 3):- 
    !.
next_factor(N, F, NF):- 
    F * F < N, 
    !, 
    NF is F + 2.
next_factor(N, _, N).

factor_concat(Factors, Atom):-
    factor_concat(Factors, '', Atom).
factor_concat([], Atom, Atom).
factor_concat([H|T], AtomAccum, Atom):-
    number_atom(H, A),
    atom_concat(AtomAccum, A, UpdatedAtomAccum),
    factor_concat(T, UpdatedAtomAccum, Atom).

home_prime(N, HomePrime):-
    prime_factors(N, Factors),
    factor_concat(Factors, A),
    number_atom(Number, A),
    fd_not_prime(Number),
    home_prime(Number, HomePrime).    
home_prime(N, HomePrime):-
    prime_factors(N, Factors),
    factor_concat(Factors, A),
    number_atom(Number, A),
    fd_prime(Number),
    HomePrime = Number. 

Sample Run


$ gprolog --consult-file prolog/ch-2.p
| ?- home_prime(16, HomePrime).

HomePrime = 31636373 ? 

(4 ms) yes
| ?- home_prime(54, HomePrime). 

HomePrime = 2333 ? 

(1 ms) yes
| ?- home_prime(108, HomePrime).

HomePrime = 23971 ? 

yes

Notes

Here we are asked to compute the Home Prime of any given number. The process for doing so is, given N to take the prime factors for N and concatenate them together. If the result is prime then we are done, that is the Home Prime of N, typically written HP(N). This is an easy process to repeat, and in many cases the computation is a very quick one. However, in some cases, the size of the interim numbers on the path to HP(N) grow extremely large and the computation bogs down. I have used the prime factorization code here in several other weekly challenges and it is quite performant but even this runs rather slowly as we are faced with extremely large numbers.

References

Challenge 168

Home Prime

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