23
xMenores(_,[],[]).
xMenores(X,[H|T],[R|Z]) :-
   xMenores(X,T,Z),
   X > H,
   R is H.

xMenores takes three parameters:

  • The first one is a number.
  • The second is a list of numbers.
  • The third is a list and is the variable that will contain the result.

The objective of the rule xMenores is obtain a list with the numbers of the list (Second parameter) that are smaller than the value on the first parameter. For example:

?- xMenores(3,[1,2,3],X).
X = [1,2].                        % expected result

The problem is that xMenores returns false when X > H is false and my programming skills are almost null at prolog. So:

?- xMenores(4,[1,2,3],X).
X = [1,2,3].                      % Perfect.

?- xMenores(2,[1,2,3],X).
false.                            % Wrong! "X = [1]" would be perfect.

I consider X > H, R is H. because I need that whenever X is bigger than H, R takes the value of H. But I don't know a control structure like an if or something in Prolog to handle this.

Please, any solution? Thanks.

repeat
  • 18,496
  • 4
  • 54
  • 166
Hernan
  • 1,149
  • 1
  • 11
  • 29
  • 2
    in SWI, try ?- [include](http://www.swi-prolog.org/pldoc/doc_for?object=include/3)(>(2),[4,1,2,3],L). – CapelliC Aug 27 '15 at 22:19
  • 3
    Yes. But the point was to make it myself, with my own code or at least to know who to solve this problem. Thanks – Hernan Aug 27 '15 at 22:37

7 Answers7

17

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.

Community
  • 1
  • 1
  • Thanks! I accepted this one because it's an improvement to the [solution by Nicholas Carey](http://stackoverflow.com/a/32260581/1812457). Perfect! – Hernan Aug 28 '15 at 17:04
  • 3
    While `include/3` often exposes non-relational behavior, it is this time - with arithmetical expressions perfect to use. – false Aug 29 '15 at 09:38
  • @repeat It is then difficult to discuss the different approaches. Will edit this answer to be a bit more explicit about the pros and cons of each solution. –  Sep 09 '15 at 00:22
  • Consider these two queries: `?- lessthan_compare([1,2,3],4,Xs).` and `?- lessthan_compare([1,2,3],X,Xs), X=4.` – repeat Sep 09 '15 at 09:04
  • @repeat Yes, obviously, `zcompare/3` will work even if 2nd and 3rd arguments are not instantiated, which is the reason why I used it, right? On the other hand, you give away the ability to compare arbitrary terms. –  Sep 09 '15 at 09:07
  • @repeat The whole point of writing this answer in this way is that writing code is an iterative process. I am as interested in the end result as in the way to get there: this is how I try to learn. –  Sep 09 '15 at 09:10
  • 3
    The version using `compare/3` may give answers that do not hold for all possible values the variables used can take. Look at http://stackoverflow.com/questions/26720685/safe-term-order. The variant using `zcompare/3` **is** safe! – repeat Sep 09 '15 at 09:18
  • Right now, you are in the lead with your implementation using `zcompare/3`... But I guess the code could shrink 50+% if you used `if_/3` and `(#>)/3` instead. 3 days remaining. tik, tok. I'd say: go for it! – repeat Sep 10 '15 at 21:28
  • @repeat "3 days remaining. tik, tok" what is this, a game show? ;) but yeah, I am quite ok with the solution as it stands, I am really not _that_ hot for imaginary internet points. –  Sep 11 '15 at 06:08
  • Dang! I probably shouldn't have written "you are in the lead" in the first sentence;) Btw. it's never about the points, always about learning. – repeat Sep 11 '15 at 07:00
  • @repeat Sure, but every one of us has a limited time on their hands. I would gladly learn from someone else's solution. And I do prefer obvious code over concise code most of the time. Since I am not experienced with using `is_/3` and `(#>)/3`, _in my eyes_ a solution using those stops being obvious. (I feel the same about lambdas in Prolog, but this is another discussion altogether.) –  Sep 11 '15 at 07:32
  • Okay, I get that! How about this? I'll take some answer using `if_/3` and `(#>)/3` and add some "in-between" code to *bridge the gap* (code that is semantically equivalent, but may still produce unneeded choicepoints). – repeat Sep 11 '15 at 07:50
  • @repeat sure, knock yourself out –  Sep 11 '15 at 07:59
  • @boris. **Alright!** May the "revision log" be my witness;) But seriously, I'm always thankful for comments pointing out issues: Not only errors / inconsistencies, but equally important, if not more so, problems like lack of clarity, "bumpy" presentation style, etc. – repeat Sep 11 '15 at 08:28
11

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).
lurker
  • 56,987
  • 9
  • 69
  • 103
  • 2
    In my view, this is by far the best solution posted so far in this thread: It is very readable and also very general. +1! Supposing of course that the problem is posed over integers, which indeed seems to be the case from the examples, and as is also typical. – mat Aug 29 '15 at 07:01
  • 2
    s(X). Nice, highly correct, but inefficient. Why not consider an answer using `if_/3` or even `if_//3`? There will be no implementation in the world that is able to make your code as it is now determinate as it should be for given N and list. – false Aug 29 '15 at 09:36
  • 2
    @false yes, I know it's inefficient and non-deterministic.I offered it as a way to "see the problem with DCG glasses", but with now efficiency warranties expressed or implied.Regarding `if_/3` and `if_//3`, I haven't (yet) become accustomed to using them. – lurker Aug 29 '15 at 10:37
  • 2
    Promise: Will put a bounty for such an implementation ASAP! – false Aug 29 '15 at 10:41
  • @repeat I made a couple of attempts using those predicates but kept ending up with the choice point. I hadn't gotten back to resolving it. – lurker Sep 08 '15 at 19:18
  • @repeat - I updated my answer to use a standard conditional. When using an `if_/3`, there's still a choice point, which I think is due to the fact that `less_than([], N)` can match an empty input list for termination, or a non-empty list in the case the remaining elements of the input are not less than `N`. I shall post this as a separate question, as you suggest, and link back to this one. Hopefully I can get to this tonight when I have a little more time. – lurker Sep 09 '15 at 11:28
  • The bounty's still in reach... join the `if_/3` revolution! – repeat Sep 13 '15 at 20:19
  • @repeat thanks for the encouragement. I tried an `if_/3` approach and still had a choice point. Haven't had time to work it further. – lurker Sep 13 '15 at 20:29
  • Thank you for trying! Will do another bounty... Don't worry: `if_/3` is here to stay—it's monotone:) – repeat Sep 14 '15 at 05:01
5

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)
  .
Nicholas Carey
  • 71,308
  • 16
  • 93
  • 135
  • 4
    In SWI "soft-cut" refers to `(*->)/2`, not `(->)/2`. – repeat Aug 27 '15 at 23:40
  • 1
    A perfect answer (+1), but note that the predicates in library(apply) are probably a better one-liner approach than findall+member, and `include/3` is identical to your last solution. –  Aug 28 '15 at 08:32
  • Thanks, perfect solution Nicholas! – Hernan Aug 28 '15 at 17:01
  • 2
    @repeat: This is not specific to SWI. Soft cut always means `if/3` or `(*->)/2` - see Negation and Control in Prolog by Lee Naish, LNCS 238 – false Aug 29 '15 at 09:43
  • 1
    Join the bounty hunt by using `tfilter/3` in a one-liner! – repeat Sep 08 '15 at 19:07
5

(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) 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]`.
repeat
  • 18,496
  • 4
  • 54
  • 166
  • 1
    See the addition to my original answer above. It is unnecessary, I feel, but since you insist :) –  Sep 08 '15 at 13:44
  • 1
    @Boris. Ok. Please explain what you mean with "it is unnecessary". – repeat Sep 08 '15 at 18:54
  • 1
    Ok, I take "unnecessary" back. Was not certain in what situation such a predicate would be needed. –  Sep 09 '15 at 00:21
5

No new code is presented in this answer.

In the following we take a detailed look at different revisions of this answer by @lurker.


Revision #1, renamed to less_than_ver1//2. By using and , the code is both very readable and versatile:

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

Let's query!

?-  phrase(less_than_ver1(N,Zs),[1,2,3,4,5]).
  N in 6..sup, Zs = [1,2,3,4,5]
; N  = 5     , Zs = [1,2,3,4]
; N  = 4     , Zs = [1,2,3]
; N  = 3     , Zs = [1,2]
; N  = 2     , Zs = [1]
; N in inf..1, Zs = []
; false.

?- N = 3, phrase(less_than_ver1(N,Zs),[1,2,3,4,5]).
  N = 3, Zs = [1,2]       % succeeds, but leaves useless choicepoint
; false.

?-        phrase(less_than_ver1(N,Zs),[1,2,3,4,5]), N = 3.
  N = 3, Zs = [1,2]
; false.

As a small imperfection, less_than_ver1//2 leaves some useless choicepoints.

Let's see how things went with the newer revision...


Revision #3, renamed to less_than_ver3//2:

less_than_ver3([],_) --> [].
less_than_ver3(L,N) --> [X], { X #< N -> L=[X|T] ; L=T }, less_than_ver3(L,N).

This code uses the if-then-else ((->)/2 + (;)/2) in order to improve determinism.

Let's simply re-run the above queries!

?- phrase(less_than_ver3(Zs,N),[1,2,3,4,5]).
  N in 6..sup, Zs = [1,2,3,4,5]
; false.                              % all other solutions are missing!

?- N = 3, phrase(less_than_ver3(Zs,N),[1,2,3,4,5]).
  N = 3, Zs = [1,2]                   % works as before, but no better.
; false.                              % we still got the useless choicepoint

?-        phrase(less_than_ver3(Zs,N),[1,2,3,4,5]), N = 3.
false.                                % no solution! 
                                      % we got one with revision #1!

Surprise! Two cases that worked before are now (somewhat) broken, and the determinism in the ground case is no better... Why?

  1. The vanilla if-then-else often cuts too much too soon, which is particularly problematic with code which uses coroutining and/or constraints.

    Note that (*->)/2 (a.k.a. "soft-cut" or if/3), fares only a bit better, not a lot!

  2. As if_/3 never ever cuts more (often than) the vanilla if-then-else (->)/2, it cannot be used in above code to improve determinism.

  3. If you want to use if_/3 in combination with constraints, take a step back and write code that is non- as the first shot.

  4. If you're lazy like me, consider using a like tfilter/3 and (#>)/3.

Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
  • 1
    Yeah sorry I need another cup of coffee... Still, you're post is very helpful in its analysis (+1). – lurker Sep 09 '15 at 12:55
  • Ok, no harm done. Don't hesitate to post independent (additional) new answers. When shifting the focus on determinism, it's easier to first consider the non-dcg case. – repeat Sep 09 '15 at 12:57
4

This answer by @Boris presented a logically pure solution which utilizes clpfd:zcompare/3 to help improve determinism in certain (ground) cases.

In this answer we will explore different ways of coding logically pure Prolog while trying to avoid the creation of useless choicepoints.


Let's get started with zcompare/3 and (#<)/3!

  • zcompare/3 implements three-way comparison of finite domain variables and reifies the trichotomy into one of <, =, or >.
  • As the inclusion criterion used by the OP was a arithmetic less-than test, we propose using (#<)/3 for reifying the dichotomy into one of true or false.

Consider the answers of the following queries:

?- zcompare(Ord,1,5), #<(1,5,B).
Ord = (<), B = true.    

?- zcompare(Ord,5,5), #<(5,5,B).
Ord = (=), B = false.   

?- zcompare(Ord,9,5), #<(9,5,B).
Ord = (>), B = false.    

Note that for all items to be selected both Ord = (<) and B = true holds.


Here's a side-by-side comparison of three non- solutions based on :

  • The left one uses zcompare/3 and first-argument indexing on the three cases <, =, and >.
  • The middle one uses (#<)/3 and first-argument indexing on the two cases true and false.
  • The right one uses (#<)/3 in combination with if_/3.

Note that we do not need to define auxiliary predicates in the right column!

less_than([],[],_).       % less_than([],[],_).          % less_than([],[],_).
less_than([Z|Zs],Ls,X) :- % less_than([Z|Zs],Ls,X) :-    % less_than([Z|Zs],Ls,X) :-
   zcompare(Ord,Z,X),     %    #<(Z,X,B),                %    if_(Z #< X,
   ord_lt_(Ord,Z,Ls,Rs),  %    incl_lt_(B,Z,Ls,Rs),      %        Ls = [Z|Rs],
   less_than(Zs,Rs,X).    %    less_than(Zs,Rs,X).       %        Ls = Rs),
                          %                              %    less_than(Zs,Rs,X).   
ord_lt_(<,Z,[Z|Ls],Ls).   % incl_lt_(true ,Z,[Z|Ls],Ls). %
ord_lt_(=,_,   Ls ,Ls).   % incl_lt_(false,_,   Ls ,Ls). %    
ord_lt_(>,_,   Ls ,Ls).   %                              % 

Next, let's use !

  • In the right column we use if_//3 instead of if_/3.
  • Note the different argument orders of and non- solutions: less_than([1,2,3],Zs,3) vs phrase(less_than([1,2,3],3),Zs).

The following implementations correspond to above non- codes:

less_than([],_) --> [].   % less_than([],_) --> [].      % less_than([],_) --> [].  
less_than([Z|Zs],X) -->   % less_than([Z|Zs],X) -->      % less_than([Z|Zs],X) -->  
   { zcompare(Ord,Z,X) }, %    { #<(Z,X,B) },            %    if_(Z #< X,[Z],[]),
   ord_lt_(Ord,Z),        %    incl_lt_(B,Z),            %    less_than(Zs,X).     
   less_than(Zs,X).       %    less_than(Zs,X).          %
                          %                              %  
ord_lt_(<,Z) --> [Z].     % incl_lt_(true ,Z) --> [Z].   % 
ord_lt_(=,_) --> [].      % incl_lt_(false,_) --> [].    %
ord_lt_(>,_) --> [].      %                              % 

OK! Saving the best for last... Simply use tfilter/3 together with (#>)/3!

less_than(Xs,Zs,P) :-
   tfilter(#>(P),Xs,Zs).
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
1

The variant in this previous answer is our starting point.

Consider the auxiliary non-terminal ord_lt_//2:

ord_lt_(<,Z) --> [Z].
ord_lt_(=,_) --> [].
ord_lt_(>,_) --> [].

These three clauses can be covered using two conditions:

  1. Ord = (<): the item should be included.
  2. dif(Ord, (<)): it should not be included.

We can express this "either-or choice" using if_//3:

less_than([],_) --> [].
less_than([Z|Zs],X) -->
   { zcompare(Ord,Z,X) },
   if_(Ord = (<), [Z], []),
   less_than(Zs,X).

Thus ord_lt_//2 becomes redundant.

Net gain? 3 !-)

repeat
  • 18,496
  • 4
  • 54
  • 166