RabbitFarm

2022-03-20

The Weekly Challenge 156 (Prolog Solutions)

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

Part 1

Write a script to generate the first 10 Pernicious Numbers.

Solution


pernicious(_) --> [].
pernicious(Seen) --> [X], x(Seen, X), {set_bits(X, Bits), fd_prime(Bits)}, pernicious([X|Seen]).
x(Seen, X) --> {between(1, 100, X), \+ member(X, Seen)}. 

set_bits(N, X):-
    set_bits(N, 0, X).
set_bits(0, X, X).
set_bits(N, X_Acc, X):-
    B is N /\ 1,
    X0 is X_Acc + B,
    N0 is N >> 1,
    set_bits(N0, X0, X), !.

Sample Run


$ gprolog --consult-file prolog/ch-1.p
| ?- length(Pernicious, 10), phrase(pernicious([]), Pernicious).

Pernicious = [3,5,6,7,9,10,11,12,13,14] ? 

(115 ms) yes
| ?- phrase(pernicious([]), [3, 5, 6]).

true ? 

(95 ms) yes

Notes

DCGs are great aren't they? The ability to have two modes, one to test and the other to create is a joy! The logic here is pretty straightforward and more or less follows straight fromt he definition.

Part 2

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

Solution


weird(_) --> [].
weird(Seen) --> [X], x(Seen, X), {
    findall(F, factor(X, F), Factors), flatten([1, Factors], FlatFactors),
    sum_list(FlatFactors, FactorSum), 
    FactorSum > X, 
    powerset(FlatFactors, FactorSets),
    maplist(sum_list, FactorSets, FactorSetSums),
    \+ member(X, FactorSetSums)
    }, 
    weird([X|Seen]).
x(Seen, X) --> {between(1, 1000, X), \+ member(X, Seen)}. 

powerset(X,Y):- bagof(S, subseq(S,X), Y).
subseq([], []).
subseq([], [_|_]).
subseq([X|Xs], [X|Ys] ):- subseq(Xs, Ys).
subseq([X|Xs], [_|Ys] ):- append(_, [X|Zs], Ys), subseq(Xs, Zs).

factor(N, Factors):-
    S is round(sqrt(N)),
    fd_domain(X, 2, S),
    R #= N rem X,
    R #= 0,
    Q #= N // X,
    Q #\= X,
    fd_labeling([Q, X]),
    Factors = [Q, X].
factor(N, Factors):-
    S is round(sqrt(N)),
    fd_domain(X, 2, S),
    R #= N rem X,
    R #= 0,
    Q #= N // X,
    Q #= X,
    fd_labeling([Q]),
    Factors = [Q].   

Sample Run


$ gprolog --consult-file prolog/ch-2.p
| ?- phrase(weird([]), [70]).               

true ? 

yes
| ?- length(Weird, 1), phrase(weird([]), Weird).

Weird = [70] ? 

(4 ms) yes

Notes

This solution follows the same generate and test approach I used in the Perl Solution, as far as the testing of the powerset of divisors is concerned anyway. (I'll admit I was too lazy to write my own powerset code so I grabbed someone else's. See the references for a link to the source.)

In my ongoing attempts to improve my DCG skills I implemented this as a DCG which is a bit of overkill for this problem, but it is always nice to be able to generate the sequence as well as validate.

References

Challenge 156

Pernicious Number

Weird Number

Power Set

posted at: 18:26 by: Adam Russell | path: /prolog | permanent link to this entry