Numbers in a list smaller than a given number

(This is more like a comment than an answer, but too long for a comment.)

Some previous answers and comments have suggested using "if-then-else" (->)/2 or using library(apply) meta-predicate include/3. Both methods work alright, as long as only plain-old Prolog arithmetics—is/2, (>)/2, and the like—are used ...

?- X = 3, include(>(X),[1,3,2,5,4],Xs).
X = 3, Xs = [1,2].

?-        include(>(X),[1,3,2,5,4],Xs), X = 3.
ERROR: >/2: Arguments are not sufficiently instantiated
% This is OK. When instantiation is insufficient, an exception is raised.

..., but when doing the seemingly benign switch from (>)/2 to (#>)/2, we lose soundness!

?- X = 3, include(#>(X),[1,3,2,5,4],Xs).
X = 3, Xs = [1,2].

?-        include(#>(X),[1,3,2,5,4],Xs), X = 3.
false.
% This is BAD! Expected success with answer substitutions `X = 3, Xs = [1,2]`.

You could write it as a one-liner using findall\3:

filter( N , Xs , Zs ) :- findall( X, ( member(X,Xs), X < N ) , Zs ) .

However, I suspect that the point of the exercise is to learn about recursion, so something like this would work:

filter( _ , []     , []     ) .
filter( N , [X|Xs] , [X|Zs] ) :- X <  N , filter(N,Xs,Zs) .
filter( N , [X|Xs] , Zs     ) :- X >= N , filter(N,Xs,Zs) .

It does, however, unpack the list twice on backtracking. An optimization here would be to combine the 2nd and 3rd clauses by introducing a soft cut like so:

filter( _ , []     , []     ) .
filter( N , [X|Xs] , [X|Zs] ) :-
  ( X < N -> Zs = [X|Z1] ; Zs = Z1 ) ,
  filter(N,Xs,Zs)
  .

Using ( if -> then ; else )

The control structure you might be looking for is ( if -> then ; else ).

Warning: you should probably swap the order of the first two arguments:

lessthan_if([], _, []).
lessthan_if([X|Xs], Y, Zs) :-
    (   X < Y
    ->  Zs = [X|Zs1]
    ;   Zs = Zs1
    ),
    lessthan_if(Xs, Y, Zs1).

However, if you are writing real code, you should almost certainly go with one of the predicates in library(apply), for example include/3, as suggested by @CapelliC:

?- include(>(3), [1,2,3], R).
R = [1, 2].

?- include(>(4), [1,2,3], R).
R = [1, 2, 3].

?- include(<(2), [1,2,3], R).
R = [3].

See the implementation of include/3 if you want to know how this kind of problems are solved. You will notice that lessthan/3 above is nothing but a specialization of the more general include/3 in library(apply): include/3 will reorder the arguments and use the ( if -> then ; else ).

"Declarative" solution

Alternatively, a less "procedural" and more "declarative" predicate:

lessthan_decl([], _, []).
lessthan_decl([X|Xs], Y, [X|Zs]) :- X < Y,
    lessthan_decl(Xs, Y, Zs).
lessthan_decl([X|Xs], Y, Zs) :- X >= Y,
    lessthan_decl(Xs, Y, Zs).

(lessthan_if/3 and lessthan_decl/3 are nearly identical to the solutions by Nicholas Carey, except for the order of arguments.)

On the downside, lessthan_decl/3 leaves behind choice points. However, it is a good starting point for a general, readable solution. We need two code transformations:

  1. Replace the arithmetic comparisons < and >= with CLP(FD) constraints: #< and #>=;
  2. Use a DCG rule to get rid of arguments in the definition.

You will arrive at the solution by lurker.

A different approach

The most general comparison predicate in Prolog is compare/3. A common pattern using it is to explicitly enumerate the three possible values for Order:

lessthan_compare([], _, []).
lessthan_compare([H|T], X, R) :-
    compare(Order, H, X),
    lessthan_compare_1(Order, H, T, X, R).

lessthan_compare_1(<, H, T, X, [H|R]) :-
    lessthan_compare(T, X, R).
lessthan_compare_1(=, _, T, X, R) :-
    lessthan_compare(T, X, R).
lessthan_compare_1(>, _, T, X, R) :-
    lessthan_compare(T, X, R).

(Compared to any of the other solutions, this one would work with any terms, not just integers or arithmetic expressions.)

Replacing compare/3 with zcompare/3:

:- use_module(library(clpfd)).

lessthan_clpfd([], _, []).
lessthan_clpfd([H|T], X, R) :-
    zcompare(ZOrder, H, X),
    lessthan_clpfd_1(ZOrder, H, T, X, R).

lessthan_clpfd_1(<, H, T, X, [H|R]) :-
    lessthan_clpfd(T, X, R).
lessthan_clpfd_1(=, _, T, X, R) :-
    lessthan_clpfd(T, X, R).
lessthan_clpfd_1(>, _, T, X, R) :-
    lessthan_clpfd(T, X, R).

This is definitely more code than any of the other solutions, but it does not leave behind unnecessary choice points:

?- lessthan_clpfd(3, [1,3,2], Xs).
Xs = [1, 2]. % no dangling choice points!

In the other cases, it behaves just as the DCG solution by lurker:

?- lessthan_clpfd(X, [1,3,2], Xs).
Xs = [1, 3, 2],
X in 4..sup ;
X = 3,
Xs = [1, 2] ;
X = 2,
Xs = [1] ;
X = 1,
Xs = [] .

?- lessthan_clpfd(X, [1,3,2], Xs), X = 3. %
X = 3,
Xs = [1, 2] ; % no error!
false.

?- lessthan_clpfd([1,3,2], X, R), R = [1, 2].
X = 3,
R = [1, 2] ;
false.

Unless you need such a general approach, include(>(X), List, Result) is good enough.


This can also be done using a DCG:

less_than([], _) --> [].
less_than([H|T], N) --> [H], { H #< N }, less_than(T, N).
less_than(L, N) --> [H], { H #>= N }, less_than(L, N).

| ?- phrase(less_than(R, 4), [1,2,3,4,5,6]).

R = [1,2,3] ? ;

You can write your predicate as:

xMenores(N, NumberList, Result) :- phrase(less_than(Result, N), NumberList).

Tags:

List

Prolog