RabbitFarm

2022-06-19

The Weekly Challenge 169 (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 20 Brilliant Numbers.

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).

brilliants(_) --> [].
brilliants(Seen) --> [X], {brilliant(X), \+ member(X, Seen)}, brilliants([X|Seen]).

brilliant(X):-
    current_prolog_flag(max_integer, MAX_INTEGER),
    between(1, MAX_INTEGER, X),
    prime_factors(X, Factors),
    length(Factors, 2),
    nth(1, Factors, First),
    nth(2, Factors, Second),
    number_chars(First, FirstChars),
    number_chars(Second, SecondChars),
    length(FirstChars, FirstCharsLength),
    length(SecondChars, SecondCharsLength),
    FirstCharsLength == SecondCharsLength.

n_brilliants(N, Brilliants):-
    length(Brilliants, N), 
    phrase(brilliants([]), Brilliants). 

Sample Run


$ gprolog --consult-file prolog/ch-1.p 
| ?- n_brilliants(20, Brilliants).

Brilliants = [4,6,9,10,14,15,21,25,35,49,121,143,169,187,209,221,247,253,289,299] ? 

Notes

The use of a DCG here seems appropriate as we are generating a sequence of numbers of a DCG will allow us to reason on such lists. The logic for inclusion in the sequence is a bit complex and so it further seems natural to break that into its own predicate. That is not required, of course, but in terms of pure style it seems the DCG starts to look clunky or overstuffed when containing a lot of Prolog code in curly braces. Perhaps that is especially true here where we further need additional predicates for computing the prime factors.

Part 2

Write a script to generate the first 20 Achilles Numbers.

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).

powerful(N, X):-
    M is mod(N, X * X),
    M == 0.

imperfect(N):-
    Sqrt is round(sqrt(N)),
    S is Sqrt - 1,
    length(I, S),
    fd_domain(I, 2, Sqrt),
    fd_all_different(I),
    fd_labeling(I),!,
    maplist(imperfect(N), I).
imperfect(N, X):-
    D is log(N) / log(X),
    Check is abs(D - round(D)),
    \+ Check < 0.000001.

achilles(_) --> [].
achilles(Seen) --> [X], {current_prolog_flag(max_integer, MAX_INTEGER), 
                         between(2, MAX_INTEGER, X), \+ member(X, Seen), achilles(X)}, 
                   achilles([X|Seen]).

achilles(X):-
    prime_factors(X, Factors), 
    maplist(powerful(X), Factors),
    imperfect(X).

n_achilles(N, Achilles):-
    length(Achilles, N), 
    phrase(achilles([]), Achilles). 

Sample Run


$ gprolog --consult-file prolog/ch-2.p
| ?- n_achilles(20, Achilles).

Achilles = [72,108,200,288,392,432,500,648,675,800,864,968,972,1125,1152,1323,1352,1372,1568,1800] ? 

Notes

The approach here for the second task is similar to that of the first. Somewhat surprisingly while the conditions of this sequence are more complex the code itself is represented in a cleaner way. I attribute that to the use of maplist/2 which streamlines the checking of lists for the two criteria of Achilles numbers: that they are powerful but imperfect.

References

Challenge 169

posted at: 12:39 by: Adam Russell | path: /prolog | permanent link to this entry