RabbitFarm

2022-07-03

The Weekly Challenge 171 (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 twenty Abundant Odd Numbers.

Solution


proper_divisors(X, Divisors):-
    Half is X // 2,
    findall(Divisor,(
        between(1, Half, Divisor),
        M is mod(X, Divisor),
        M == 0
    ), Divisors).

abundants_odd(_) --> [].
abundants_odd(Previous) --> [X], {abundant_odd(Previous, X)}, abundants_odd(X).

abundant_odd(Previous, X):-
    current_prolog_flag(max_integer, MAX_INTEGER),
    between(Previous, MAX_INTEGER, X),
    X > Previous,
    M is mod(X, 2),
    M == 1,
    proper_divisors(X, Divisors),
    sum_list(Divisors, DivisorsSum),
    DivisorsSum > X.

n_abundants(N, Abundants):-
    length(Abundants, N), 
    phrase(abundants_odd(-1), Abundants). 

Sample Run


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

Abundants = [945,1575,2205,2835,3465,4095,4725,5355,5775,5985,6435,6615,6825,7245,7425,7875,8085,8415,8505,8925] ? 

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.

Part 2

Create sub compose($f, $g) which takes in two parameters $f and $g as subroutine refs and returns subroutine ref i.e. compose($f, $g)->($x) = $f->($g->($x)).

Solution


f(S, T):-
    T is S + S.

g(S, T):-
    T is S * S.

compose(F, G, H):-
    asserta((h(X, Y) :- call(G, X, X0), call(F, X0, Y))),
    H = h.

Sample Run


$ gprolog --consult-file prolog/ch-2.p
| ?- compose(f, g, H), A =.. [H, 7, X], A.

A = h(7,98)
H = h
X = 98

yes
| ?- 

Notes

This challenge is posed as being Perl specific and while most any language is able to do more or less what is asked for, this is a bit of a strange thing to do in Prolog.

In general, Prolog would dicate the use of a meta-interpreter for this sort of thing, instead of this sort of Functional Programming practice. Sticking to the letter of the challenge I was able to cobble something together with asserta/1 and the univ operator (=..)/2.

An assumption made in my code is that we know ahead of time the number of arguments to predicates F and G and that we also know which variables are instantiated or not. Those assumptions greatly simplify things and we can compose the two predicates in this way. Without that assumption the code would explode in complexity as we would need to examine whether variables are instantiated or not and then make possibly incorrect new assumptions that they, in fact, should have been or not.

References

Challenge 171

A Couple of Meta-interpreters in Prolog

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