Question

Just got introduced to prolog, trying to get through some simple exercises, but I've been getting kind of stuck on this one. I'm trying to write a program that outputs all the sublists of the input list, where each sublist has length > 1 and it cannot be extended to a larger sublist. It will also output the starting position in the list of the sublist. So a sample output would be

| ?- plateau([a,a,b,2,2,2,a+1,a+1,s(1,2)], I, Len).
    I = 1,
    Len = 2 ? ;
    I = 4,
    Len = 3 ? ;
    I = 7,
    Len = 2 ? ;
    no

I'm still pretty confused by the whole declarative thing, and having a lot of trouble switching out of imperative mode. I'm thinking I want my program to do something like

program([H|T],I,L):-
    T = [H1|T1] %split the tail
    ([H] = [H1] -> Count is Count+1, program(T,I,Count) 
     %if First element = second element, recurse with new values
    ; length(T,Spot), 
      %get the spot where you are in the list, so we know where sublist starts
      program(T,Spot,L) %run again, from tail, since sublist didn't have another  element?
program([],I,L). %terminate when entire list has been run through?

So this isn't working, from what I can tell for a couple reasons. I don't reset 'count', so its totaling up the values of all the sublists together maybe? Is there some way to work around for this? My base case might also not be what I want - I'm just not sure what it should be really? I'm probably missing other things too...any help is greatly appreciated! :) Thanks!

Was it helpful?

Solution

There are quite a lot of complicated answers here. Consider this one which doesn't use DCGs or many built-ins (perhaps simpler for a beginner):

plateau([X|Xs], I, L) :-
    plateau(Xs, 1-1-X, I, L).

plateau([X1|Xs], I0-L0-X0, I, L) :-
    X0 == X1, !,
    NL0 is L0 + 1,
    plateau(Xs, I0-NL0-X0, I, L).

plateau(_, I-L-_, I, L) :-
    L > 1.

plateau([X|Xs], I0-L0-_, I, L) :-
    NI is I0 + L0,
    plateau(Xs, NI-1-X, I, L).

The first clause sets up the call which accumulates the (index)-(length)-(sublist element) tuple, as a term.

The next clause increments the length if the next list element is the same (note the index isn't altered).

The third clause is called only if the second clause failed when testing if the sublist element run was broken (because of the cut !), and returns a solution iff the length of the run was > 1.

The last clause enables Prolog to backtrack and re-start the search from the last run.

EDIT: gusbro's solution is actually very close to this one... +1.

OTHER TIPS

Your program combines many different issues into one predicate. Let's try to separate those a bit. Also, I assume you are searching for a maximal sublist of two or more elements containing identical elements.

Let's start with an approximation of what you want: Identifying sublists. Don't worry that this is way too broad, we will refine it later on. I will use DCGs for this purpose. The non-terminal seq//1 describes an arbitrary sequence.

seq([]) --> [].
seq([E|Es]) --> [E], seq(Es).

This is an extremely useful non-terminal!

?- phrase((seq(Prefix),seq(Sublist),seq(Postfix)),
      [a,a,b,2,2,2,a+1,a+1,s(1,2)]).
Prefix = Sublist, Sublist = [],
Postfix = [a,a,b,2,2,2,a+1,a+1,s(1,2)] ;
Prefix = [],
Sublist = "a",
Postfix = [a,b,2,2,2,a+1,a+1,s(1,2)] ...

Both answers are not expected, we only want sublists of length 2 or more, so we have to restrict that definition a bit. Say, by demanding that Sublist should contain at least two elements. That is Sublist = [_,_|_].

?- Sublist = [_,_|_],
   phrase((seq(Prefix),seq(Sublist),seq(Postfix)),
      [a,a,b,2,2,2,a+1,a+1,s(1,2)]).
Sublist = "aa",
Prefix = [],
Postfix = [b,2,2,2,a+1,a+1,s(1,2)] ;
Sublist = "aab",
Prefix = [],
Postfix = [2,2,2,a+1,a+1,s(1,2)] ...

The first answer shows a sublist we are searching for. But the second is still incorrect: All elements of the sublist should be equal. The easiest way is to use maplist/2:

?- maplist(=(_),Es).
Es = [] ;
Es = [_G221] ;
Es = [_G221,_G221] ;
Es = [_G221,_G221,_G221] 

There are several places where we could state that requirement. I will put it at the earliest place possible:

?- Sublist = [_,_|_],
        phrase(( seq(Prefix),
                 seq(Sublist),{maplist(=(_),Sublist)},
                 seq(Postfix)),
           [a,a,b,2,2,2,a+1,a+1,s(1,2)]).
Sublist = "aa",
Prefix = [],
Postfix = [b,2,2,2,a+1,a+1,s(1,2)] ;
Sublist = [2,2],
Prefix = "aab",
Postfix = [2,a+1,a+1,s(1,2)] ;
Sublist = [2,2,2],
Prefix = "aab",
Postfix = [a+1,a+1,s(1,2)] ;
Sublist = [2,2],
Prefix = [a,a,b,2],
Postfix = [a+1,a+1,s(1,2)] ;
Sublist = [a+1,a+1],
Prefix = [a,a,b,2,2,2],
Postfix = [s(1,2)] ;
false.

So now, all sublists contain identical elements. Alas, we get both [2,2] and [2,2,2] as sublist. We only want the maximal sublist. So how can we describe what a maximal sublist is?

One way is to look in front of our sublist: There must not be the very same element of our sublist. Thus, either there is nothing (epsilon) in front, or a sequence which ends with an element different to ours.

difel(_E,[]).
difel(E, Es) :- dif(E,F), phrase((seq(_), [F]), Es).
?- Sublist = [_,_|_],
   phrase(( seq(Prefix),{difel(E,Prefix)},
            seq(Sublist),{maplist(=(E),Sublist)},
            seq(Postfix)),
      [a,a,b,2,2,2,a+1,a+1,s(1,2)]).
Sublist = "aa",
Prefix = [],
E = a,
Postfix = [b,2,2,2,a+1,a+1,s(1,2)] ;
Sublist = [2,2],
Prefix = "aab",
E = 2,
Postfix = [2,a+1,a+1,s(1,2)] ;
Sublist = [2,2,2],
Prefix = "aab",
E = 2,
Postfix = [a+1,a+1,s(1,2)] ;
Sublist = [a+1,a+1],
Prefix = [a,a,b,2,2,2],
E = a+1,
Postfix = [s(1,2)] ;
false.

One incorrect answer less. There is still one lurking around at the end.

?- Sublist = [_,_|_],
   phrase(( seq(Prefix),{difel(E,Prefix)},
            seq(Sublist),{maplist(=(E),Sublist)},
            ( [] | [F],{dif(E,F)},seq(_) ) ),
      [a,a,b,2,2,2,a+1,a+1,s(1,2)]).
Sublist = "aa",
Prefix = [],
E = a,
F = b ;
Sublist = [2,2,2],
Prefix = "aab",
E = 2,
F = a+1 ;
Sublist = [a+1,a+1],
Prefix = [a,a,b,2,2,2],
E = a+1,
F = s(1,2) ;
false.

That is not exactly what you wanted: You simply wanted the lengths. For this, add length([_|Prefix],I), length(Sublist,Len).

So here is the final definition:

plateau(Xs, I, Len) :-
   Sublist = [_,_|_],
   phrase(( seq(Prefix),{difel(E,Prefix)},
            seq(Sublist),{maplist(=(E),Sublist)},
            ( [] | [F],{dif(E,F)},seq(_) ) ),
      Xs),
   length([_|Prefix],I),
   length(Sublist,Len).

I tried using nth1/3 builtin, but had more trouble to get it working... anyway, here another implementation:

plateau(L, I, Len) :-
    plateau(L, 1, I, Len).
plateau(L, P, I, Len) :-
    nth1(P, L, E),
    skipseq(P, L, E, J),
    (   J > P,
        Len is J - P + 1,
        I is P
    ;   Q is J + 1,
        plateau(L, Q, I, Len)
    ).

% get the index J of last element E (after I)
skipseq(I, L, E, J) :-
    T is I + 1,
    nth1(T, L, E),
    !, skipseq(T, L, E, J).
skipseq(I, _, _, I).

test:

[debug]  ?- plateau([a,x,x,x,u,u,h,w],I,N).
I = 2,
N = 3 ;
I = 5,
N = 2 ;
false.

You could do something like this:

plateau([Item|Tail], I, Len):-
  plateau(Tail, 1, Item, 1, I, Len).

plateau(List, From, NItem, Len, From, Len):-
  (List=[Item|_] -> (Item\=NItem;var(Item)); List = []),
  Len > 1.
plateau([Item|Tail], IFrom, Item, ILen, From, Len):-
  MLen is ILen + 1,
  plateau(Tail, IFrom, Item, MLen, From, Len).
plateau([Item|Tail], IFrom, OItem, ILen, From, Len):-
  OItem \= Item,
  NFrom is IFrom + ILen,
  plateau(Tail, NFrom, Item, 1, From, Len).

The first clause of plateau/6 deals with the termination of the sublist. It is either the case that the item is different from the one you are looking or you reached the end of the list. In that case we only proceed if the current length is greater than one.

The second clause deals with the recursion step for the case the we are still matching the element in the list. It just adds one to the counter of current sublist and does the recursion.

The last clause deals with the case of a new (different) item found in the list and just resets the counters and does recursion.

This is straightforward and simple. We count from 1; plateau is a maximal subsequence of equal elements, at least 2 in length; we proceed along the list. Just write it down:

plateau(L,I,N):- plateau(L,1,I,N).                     % count from 1

plateau([A,A|B],I1,I,N):- !, more_elts(A,B,2,K,C),     % two equals, or more
    (I is I1, N is K ; plateau(C,I1+K,I,N)).
plateau([_|B],I1,I,N):- plateau(B,I1+1,I,N).           % move along the list

more_elts(A,[A|B],I,K,C):- !, more_elts(A,B,I+1,K,C).
more_elts(_,B,I,I,B).

update: This assumes all the elements of the input list are nonvar/1. Having non-instantiated variables as input list's elements here makes the notion of "sublist" tricky and vague. E.g., what are the sublists of [a,X,b,b]? Can [a,a] and [b,b,b] both be sublists of the same input list? (this reminds me of observable values of spin, superpositions of states, etc. somehow... When a direction of spin observation is chosen, it can not be changed anymore... cf. all the talk about "measurement" and quantum mechanics in sokuza-kanren.scm (found that link here))

Licensed under: CC-BY-SA with attribution
Not affiliated with StackOverflow
scroll top