5

Given a prolog list I want to create a second one containing the progressively bigger elements. For example,

L = [ 1, 5, 2, 3, 4, 10, 15, 11, 12, 13, 20 ]

Answer = [ 1, 5, 10, 15, 20 ]

My code:

local_max([],_,_).
local_max([XH|XT],Y,temp) :-
    ( XH =< temp ->
      local_max(XT,Y,temp)
      ;
      local_max(XT,[XH|Y],XH)
    ).

I thought this should produce my answered simply reversed but it doesn't. Just false.

The list contains only positive integers so I simply did

local_max([ 1, 5, 2, 3, 4, 10, 15, 11, 12, 13, 20 ],Answer,0).
Sergey Kalinichenko
  • 714,442
  • 84
  • 1,110
  • 1,523
cgss
  • 233
  • 2
  • 10

2 Answers2

5

Since you are using Prolog's (;)/2 - if-then-else for the task, you might like to consider if_/3. In addition the predicate can be made more versatile by using CLP(FD) (for details see e.g. the Swi-Prolog manual's entry on CLP(FD)). And furthermore I would suggest to use a calling predicate with two arguments, namely the list and the sublist of progressively ascending elements. To emphasize the relational nature of the predicate let's give it a more descriptive name, say list_ascendings/2:

:- use_module(library(clpfd)).

list_ascendings([],[]).
list_ascendings([X|Xs],A) :-
   X0 #= X-1,
   list_ascendings_([X|Xs],A,X0).

The first rule of list_ascendings/2 is for handling the empty list. If you don't want to include that case just omit the rule. The second rule calls the predicate list_ascendings_/3 with a pivot value (X0) that's smaller than the head of the list, so the latter is included in the sublist of progressively ascending elements. A reifying version of the greater than relation (used as the first argument of if_/3) can be defined like so:

bool_t(1,true).
bool_t(0,false).

#<(X,Y,Truth)  :- X #< Y #<==> B, bool_t(B,Truth).

Building on this, the predicate describing the actual relation can be defined like so:

list_ascendings_([],[],_).
list_ascendings_([X|Xs],A,X0) :-
   if_(X0#<X, (A=[X|As], X1=X), (A=As, X1=X0)), 
   list_ascendings_(Xs,As,X1).

Depending on whether the pivot value is smaller than the head of the list or not, the list of ascending elements (A) and the new pivot value (X1) are described accordingly.

Now let's see how the predicate works. Your example query yields the desired result:

   ?- list_ascendings([1,5,2,3,4,10,15,11,12,13,20],A).
A = [1,5,10,15,20]

Note that the predicate is succeeding deterministically if the first argument is ground (no choicepoints left open therefore no need to press ; after the unique solution). You can also ask the opposite question: Which lists have [1,5,10,15,20] as the biggest progressively ascending sublist?

   ?- list_ascendings(L,[1,5,10,15,20]).
L = [1,5,10,15,20] ? ;
L = [1,5,10,15,20,_A],
_A in inf..20 ? ;
L = [1,5,10,15,20,_A,_B],
_A in inf..20,
_B in inf..20 ? 
...

Obviously there are infinitely many answers to that question. However, it would be nice to get the answers in a fairer order, that is all answers for lists of length 6 before lists of length 7 and so on. You can achieve that by prefixing the query with a goal length/2:

   ?- length(L,_), list_ascendings(L,[1,5,10,15,20]).
L = [1,5,10,15,20] ? ;
L = [1,5,10,15,20,_A],
_A in inf..20 ? ;
L = [1,5,10,15,_A,20],
_A in inf..15 ? ;
L = [1,5,10,_A,15,20],
_A in inf..10 ? ;
...
L = [1,5,10,15,20,_A,_B],
_A in inf..20,
_B in inf..20 ? ;
L = [1,5,10,15,_A,20,_B],
_A in inf..15,
_B in inf..20 ? ;
L = [1,5,10,15,_A,_B,20],
_A in inf..15,
_B in inf..15 ? ;
...

You can also get answers with concrete numbers by restricting the elements of L to a domain using ins/2 and labeling it. For example: Which lists of length 7 and numbers between 0 and 20 are there such that [1,5,10,15,20] is the biggest progressively ascending sublist? The according query delivers all 1997 answers:

   ?- length(L,7), L ins 0..20, list_ascendings(L,[1,5,10,15,20]), label(L).
L = [1,5,10,15,20,0,0] ? ;
L = [1,5,10,15,20,0,1] ? ;
L = [1,5,10,15,20,0,2] ? ;
...
L = [1,5,10,15,20,2,15] ? ;
...
L = [1,0,5,10,4,15,20] ? ;
...

EDIT:

Concerning your question in the comments, describing the progressively descending sublist is pretty straightforward coming from the ascending version. You just need to slightly alter two goals:

list_descendings([],[]).
list_descendings([X|Xs],A) :-
   X0 #= X+1,                                     % <- change
   list_descendings_([X|Xs],A,X0).

list_descendings_([],[],_).
list_descendings_([X|Xs],A,X0) :-
   if_(X#<X0, (A=[X|As], X1=X), (A=As, X1=X0)),   % <- change
   list_descendings_(Xs,As,X1).

Which yields the desired result:

   ?- list_descendings([20,15,3,5,7,8,2,6,2],A).
A = [20,15,3,2]

On the other hand, if you mean one predicate that does both (see the last query below) you need a few more changes. First you need to add a reifying version of the relation for descending sublists:

#>(X,Y,Truth)  :- X #> Y #<==> B, bool_t(B,Truth).

Since the first pivot value is calculated differently for ascending and descending sublists, it is oppurtune to delegate that to a new predicate:

x_pivot_wrt(X,X0,#>) :- X0 #= X+1.
x_pivot_wrt(X,X0,#<) :- X0 #= X-1.

Then the calling predicate needs an additional argument to specify with respect to which relation the sublist shall be progressing. It would also be favorable to rename it to reflect its new behaviour:

list_progressives_wrt([],[],_).
list_progressives_wrt([X|Xs],P,Rel) :-
   x_pivot_wrt(X,X0,Rel),
   list_progressives_wrt_([X|Xs],P,Rel,X0).

Finally the predicate that's describing the actual relation also has an additional argument, namely the specified relation. The first argument of if_/3 calls the specified relation (Rel) together with the pivot value (X0) and the head of the list (X). Note that the call is lacking the last argument (the truth value) just like the first argument of if_/3 in list_ascendings_/3 and list_descendings_/3.

list_progressives_wrt_([],[],_,_).
list_progressives_wrt_([X|Xs],P,Rel,X0) :-
   if_(call(Rel,X0,X), (P=[X|Ps], X1=X), (P=Ps, X1=X0)),
   list_progressives_wrt_(Xs,Ps,Rel,X1).

The query corresponding to your example yields the desired result:

   ?- list_progressives_wrt([1,5,2,3,4,10,15,11,12,13,20],P,#<).
P = [1,5,10,15,20]

Since the relations that can be specified appear in x_pivot_wrt/3, you can ask for both variants by leaving the last argument variable:

   ?- list_progressives_wrt([20,15,3,21,5,7,8,2,6,30,2],P,Rel).
P = [20,15,3,2],
Rel = #> ? ;
P = [20,21,30],
Rel = #<
tas
  • 8,100
  • 3
  • 14
  • 22
  • 1
    Thank you for your answer. Even though I am not familiar with all those predicates you use(haven't yet seen if/3), I understand it's very good. And make the predicate flexible was interesting too. I admit in my case it can't be used but I will study it a bit. EDIT: I have although made a second predicate for doing the descending job. So, do you think it is possible to use a boolean like you did to implement both orderings at the predicate?Thanks again! – cgss Jul 10 '17 at 14:32
  • 1
    @cgss: I updated my answer to address that question. – tas Jul 10 '17 at 23:53
  • 1
    Thanks, that was awesome. I have found difficult so far to write versatile predicates but you explained it very thoroughly. – cgss Jul 11 '17 at 07:34
3

You made several small mistakes:

  • temp is not a valid variable name, it needs to be Temp,
  • _ is not a correct result when the input list is empty, it needs to be [],
  • [XH|Y] construct is not what you unify with recursive invocation on extending the list. Pass a new variable, say, R, and then build Y by unifying Y = [XH|R]

Here is your program with the fixes applied:

local_max([],[],_).
local_max([XH|XT],Y,Temp) :-
    ( XH =< Temp ->
      local_max(XT,Y,Temp)
      ;
      local_max(XT,R,XH), Y = [XH|R]
    ).

This produces your expected output (demo).

Sergey Kalinichenko
  • 714,442
  • 84
  • 1,110
  • 1,523
  • My first two mistakes were really stupid. But, as for the third one, although I understand how your codes works (and since it works I have already accepted your answer) could you please explain why mine does not unify? – cgss Jul 09 '17 at 14:44
  • @cgss Recursion needs to "bottom out" somewhere, so at some point `[XH|Y]` from `local_max(XT,[XH|Y],XH)` needs to unify with `[]` from `local_max([],[],_)`, but it cannot unify, because list `[XH|Y]` has at least one element, while list `[]` has no elements. – Sergey Kalinichenko Jul 09 '17 at 14:50
  • Yes, I see. I have to admit I din't consider that because I was too focused on my original code. I was thinking that when the original list empties then it's finished although Prolog couldn't unify [a] with _ (the same way it can't [a] with [] as you mentioned.) I got this right; – cgss Jul 09 '17 at 15:04