How to debug non-termination

80 views Asked by At

I'm trying to implement n_factors/2 predicate that works in all directions.

:- use_module(library(clpz)).

n_factors(N, Fs) :-
    integer(N),
    N > 1,
    primes(Ps),
    n_factors0(N, Fs, Ps),
    !.

n_factors(N, Fs) :-
    var(N),
    primes(Ps),
    N #> 1,
    above(2, N),
    n_factors0(N, Fs, Ps).

above(I, I).
above(I, N) :- I1 is I + 1, above(I1, N).

n_factors0(N, [F|Fs], [P|Ps]) :-
    N #> 1,
    F #=< N,
    P #=< N,
    (   P * P #> N ->
        F = N, Fs = []
        ;   (   N #= N1 * P ->
                F #= P, n_factors0(N1, Fs, [P|Ps])
            ;   F #> P, n_factors0(N, [F|Fs], Ps)
        )
    ).

When I am issuing the following query I get:

?- C #> 6, C #< 12, n_factors(A, [B,C]).
   C = 7, A = 14, B = 2
;  C = 7, A = 21, B = 3
;  C = 11, A = 22, B = 2
;  C = 11, A = 33, B = 3
;  C = 7, A = 35, B = 5
;  C = 7, A = 49, B = 7
;  C = 11, A = 55, B = 5
;  C = 11, A = 77, B = 7
;  C = 11, A = 121, B = 11
;

before the program moves on to exploring the realm of rather large numbers. So the question I've go is the following: knowing for certain that the mathematical problem is constraint enough to terminate, how do I find the missing constraint in my program? What I am doing right now is staring at the screen before trying to add "invariant" conditions here and there and see if they help.


primes(Ps) is a "frozen" infinite list with all prime numbers. I don't think the implementation thereof is important for this question but just in case

primes(Ps) :-
    Ps = [2,3|T],
    primes0(5, Ps, Ps, T),
    !.

primes0(C, [D|Ds], Ps, T) :-
    (   D * D > C ->
        T = [C|T1], C1 is C + 2, freeze(T1, primes0(C1, Ps, Ps, T1))
        ;   (   C mod D =:= 0 ->
                C1 is C + 2, primes0(C1, Ps, Ps, T)
            ;   primes0(C, Ds, Ps, T)
        )
    ).
0

There are 0 answers