Search code examples
prologclpfd

How to duplicate the behavior of predefined length/2 in SWI-Prolog?


I'm trying to duplicate the behavior of the standard length/2 predicate. In particular, I want my predicate to work for bounded and unbounded arguments, like in the example below:

% Case 1
?- length(X, Y).
X = [],
Y = 0 ;
X = [_G4326],
Y = 1 ;
X = [_G4326, _G4329],
Y = 2 ;
X = [_G4326, _G4329, _G4332],
Y = 3 .

% Case 2    
?- length([a,b,c], X).
X = 3.

% Case 3
?- length(X, 4).
X = [_G4314, _G4317, _G4320, _G4323].

% Case 4
?- length([a,b,c,d,e], 5).
true.

The plain&simple implementation:

my_length([], 0).
my_length([_|T], N) :- my_length(T, X), N is 1+X.

has some problems. In Case 3, after producing the correct answer, it goes into an infinite loop. Could this predicate be transformed into a deterministic one? Or non-deterministic that halts with false?

YES! But using red cut. See: https://stackoverflow.com/a/15123016/1545971


After some time, I've managed to code a set of predicates, that mimic the behavior of the build-in length/2. my_len_tail is deterministic and works correct in all Cases 1-4. Could it be done simpler?

my_len_tail(List, Len) :- var(Len)->my_len_tailv(List, 0, Len);
                          my_len_tailnv(List, 0, Len).

my_len_tailv([], Acc, Acc).
my_len_tailv([_|T], Acc, Len) :-
    M is Acc+1,
    my_len_tailv(T, M, Len).

my_len_tailnv([], Acc, Acc) :- !. % green!
my_len_tailnv([_|T], Acc, Len) :-
    Acc<Len,
    M is Acc+1,
    my_len_tailnv(T, M, Len).

As @DanielLyons suggested in the comments, one can use clpfd to defer less than check. But it still leaves one problem: in Case 3 (my_len_clp(X, 3)) the predicate is nondeterministic. How it could be fixed?

:-use_module(library(clpfd)).
my_len_clp(List, Len) :- my_len_clp(List, 0, Len).

my_len_clp([], Acc, Acc).
my_len_clp([_|T], Acc, Len) :-
    Acc#<Len,
    M is Acc+1,
    my_len_clp(T, M, Len).

It can be fixed using zcompare/3 from the CLP(FD) library. See: https://stackoverflow.com/a/15123146/1545971


Solution

  • In SWI-Prolog, the nondeterminism issue can be solved with CLP(FD)'s zcompare/3, which reifies the inequality to a term that can be used for indexing:

    :- use_module(library(clpfd)).
    
    my_length(Ls, L) :-
            zcompare(C, 0, L),
            my_length(Ls, C, 0, L).
    
    my_length([], =, L, L).
    my_length([_|Ls], <, L0, L) :-
            L1 #= L0 + 1,
            zcompare(C, L1, L),
            my_length(Ls, C, L1, L).
    

    Your example is now deterministic (since recent versions of SWI-Prolog perform just-in-time indexing):

    ?- my_length(Ls, 3).
    Ls = [_G356, _G420, _G484].
    

    All serious Prolog implementations ship with CLP(FD), and it makes perfect sense to use it here. Ask your vendor to also implement zcompare/3 or a better alternative if it is not already available.