Struggling with repeated floor division and clause matching in CLPFD

I’m using:

SWI-Prolog version 9.0.4 (Linux Mint Cinnamon)

I want the code to:

Find out if a number can be reduced to a multiple of another number by repeatedly applying floor division by 2, and how often that floor division by 2 has to be applied.

But what I’m getting is:

While matching the clause, it seems to never match e.g. 1-1, 2-1-1 or 3-1-1-1 to 0?

Example trace below the code.

My code looks like this:

:- use_module(library(clpfd)).

% This part works fine: checking if X can be reduced to a multiple of Y,
% without tracking how many times floor division has to be applied.
% Example use: X in 1..100, reductible(X, 4), label([X]).

reductible(0, _) :- false.

reductible(X, Y) :- 
    X #>= Y,
    X mod Y #= 0.

reductible(X, Y) :-
    X #>= Y,
    reductible((X // 2), Y).

% This part doesn't work for any Z above 0.
% Example use: reductible(8, 4, 1).

reductible(X, Y, 0) :-
    X #>= Y,
    X mod Y #= 0.

reductible(X, Y, Z) :-
    X #>= Y,
    reductible(X // 2, Y, Z - 1).

Example trace:

8 // 2 = 4, so it should register as a multiple of 4 just fine.

[trace] 22 ?- reductible(8, 4, 1).
   Call: (10) reductible(8, 4, 1) ? creep
   Call: (11) integer(8) ? creep
   Exit: (11) integer(8) ? creep
   Call: (11) integer(4) ? creep
   Exit: (11) integer(4) ? creep
   Call: (11) 8>=4 ? creep
   Exit: (11) 8>=4 ? creep
   Call: (11) reductible(8//2, 4, 1-1) ? creep
   Call: (12) integer(8//2) ? creep
   Fail: (12) integer(8//2) ? creep
   Redo: (11) reductible(8//2, 4, 1-1) ? creep
   Call: (12) integer(4) ? creep
   Exit: (12) integer(4) ? creep
   Call: (12) _19846=4 ? creep
   Exit: (12) 4=4 ? creep
   Call: (12) clpfd:clpfd_geq(8//2, 4) ? creep
   Exit: (12) clpfd:clpfd_geq(8//2, 4) ? creep
   Call: (12) reductible(8//2//2, 4, 1-1-1) ? creep
   Call: (13) integer(8//2//2) ? creep
   Fail: (13) integer(8//2//2) ? creep
   Redo: (12) reductible(8//2//2, 4, 1-1-1) ? creep
   Call: (13) integer(4) ? creep
   Exit: (13) integer(4) ? creep
   Call: (13) _28168=4 ? creep
   Exit: (13) 4=4 ? creep
   Call: (13) clpfd:clpfd_geq(8//2//2, 4) ? creep
   Fail: (13) clpfd:clpfd_geq(8//2//2, 4) ? creep
   Fail: (12) reductible(8//2//2, 4, 1-1-1) ? creep
   Fail: (11) reductible(8//2, 4, 1-1) ? creep
   Fail: (10) reductible(8, 4, 1) ? creep
false.

Same for 34 and two reductions (34 // 2 = 17, 17 // 2 = 8, 8 is a multiple of 4):

[trace] 24 ?- reductible(34, 4, 2).
   Call: (10) reductible(34, 4, 2) ? creep
   Call: (11) integer(34) ? creep
   Exit: (11) integer(34) ? creep
   Call: (11) integer(4) ? creep
   Exit: (11) integer(4) ? creep
   Call: (11) 34>=4 ? creep
   Exit: (11) 34>=4 ? creep
   Call: (11) reductible(34//2, 4, 2-1) ? creep
   Call: (12) integer(34//2) ? creep
   Fail: (12) integer(34//2) ? creep
   Redo: (11) reductible(34//2, 4, 2-1) ? creep
   Call: (12) integer(4) ? creep
   Exit: (12) integer(4) ? creep
   Call: (12) _12622=4 ? creep
   Exit: (12) 4=4 ? creep
   Call: (12) clpfd:clpfd_geq(34//2, 4) ? creep
   Exit: (12) clpfd:clpfd_geq(34//2, 4) ? creep
   Call: (12) reductible(34//2//2, 4, 2-1-1) ? creep
   Call: (13) integer(34//2//2) ? creep
   Fail: (13) integer(34//2//2) ? creep
   Redo: (12) reductible(34//2//2, 4, 2-1-1) ? creep
   Call: (13) integer(4) ? creep
   Exit: (13) integer(4) ? creep
   Call: (13) _20944=4 ? creep
   Exit: (13) 4=4 ? creep
   Call: (13) clpfd:clpfd_geq(34//2//2, 4) ? creep
   Exit: (13) clpfd:clpfd_geq(34//2//2, 4) ? creep
   Call: (13) reductible(34//2//2//2, 4, 2-1-1-1) ? creep
   Call: (14) integer(34//2//2//2) ? creep
   Fail: (14) integer(34//2//2//2) ? creep
   Redo: (13) reductible(34//2//2//2, 4, 2-1-1-1) ? creep
   Call: (14) integer(4) ? creep
   Exit: (14) integer(4) ? creep
   Call: (14) _29446=4 ? creep
   Exit: (14) 4=4 ? creep
   Call: (14) clpfd:clpfd_geq(34//2//2//2, 4) ? creep
   Exit: (14) clpfd:clpfd_geq(34//2//2//2, 4) ? creep
   Call: (14) reductible(34//2//2//2//2, 4, 2-1-1-1-1) ? creep
   Call: (15) integer(34//2//2//2//2) ? creep
   Fail: (15) integer(34//2//2//2//2) ? creep
   Redo: (14) reductible(34//2//2//2//2, 4, 2-1-1-1-1) ? creep
   Call: (15) integer(4) ? creep
   Exit: (15) integer(4) ? creep
   Call: (15) _6186=4 ? creep
   Exit: (15) 4=4 ? creep
   Call: (15) clpfd:clpfd_geq(34//2//2//2//2, 4) ? creep
   Fail: (15) clpfd:clpfd_geq(34//2//2//2//2, 4) ? creep
   Fail: (14) reductible(34//2//2//2//2, 4, 2-1-1-1-1) ? creep
   Fail: (13) reductible(34//2//2//2, 4, 2-1-1-1) ? creep
   Fail: (12) reductible(34//2//2, 4, 2-1-1) ? creep
   Fail: (11) reductible(34//2, 4, 2-1) ? creep
   Fail: (10) reductible(34, 4, 2) ? creep
false.

I’ve taken a quick look - this should help:

reductible(X, Y) :-
    X #>= Y,
    X mod Y #= 0.
reductible(X, Y) :-
    X #>= Y,
    X2 #= X // 2,
    reductible(X2, Y).

reductible(X, Y, 0) :-
    X #>= Y,
    X mod Y #= 0.
reductible(X, Y, Z) :-
    X #>= Y,
    X2 #= X // 2,
    Z0 #= Z - 1,
    reductible(X2, Y, Z0).

I’ve added the X2 and Z0 variables. And grouped the predicates with same arity together, as per standard code layout.

The reductible(0, _) :- false. line can be removed.

?- reductible(8, 4, 1).
true ;
false.

Example:

?- X = 99, Y in 2..99, R #>4, reductible(X, Y, R), label([X, Y, C]).
X = 99,
Y = 3,
C = 5 ;
false.

The variable Z could be renamed to e.g. C (short for “count”), to be more meaningful and therefore easier to work with.

It’s not quite right, with the X mod Y check - shown by:

?- reductible(8, 4, C).
C = 0 ;
C = 1 ;
false.
1 Like

Thank you so much! So my mistake was doing the arithmetic directly in the predicate call? I had no idea that would make a difference…! I guess the #= constraint is required to turn it from something like 1-1 into the actual 0?

It’s not quite right, with the X mod Y check - shown by:

?- reductible(8, 4, C).
C = 0 ;
C = 1 ;
false.

Oh, that makes sense! It’s already divisible without any reduction (8 being a multiple of 4) and again with one reduction (4 still being a multiple of 4), so there are two correct answers. For X = 9, there’s only the one:

?- reductible(9, 4, C).
C = 1 ;
false.

And again, thank you very much for the quick response!

Yup, a common Prolog gotcha - everything in Prolog is just terms, unless something specifically evaluates it, so writing reductible(X // 2, Y, Z - 1) is passing in as arguments terms like ’//’(X, 2) and ’-’(Z, 1), which in themselves have no particular meaning and need to be passed to a predicate like #= or is to create constraints or evaluate them (you can see this more clearly if you put a call to write or write_canonical in the reductible predicate to print off the arguments).

(This may seem annoying, since you end up having to write extra lines & have extra variables for every computation, but the trade-off is that its very easy to create ad-hoc terms of any structure that you need and you kind of have the equivalent of Lisp macros more-or-less for free)

2 Likes