4

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!

false
  • 10,264
  • 13
  • 101
  • 209
user1257768
  • 149
  • 1
  • 7
  • @false why the tag "DCG"? C'mon, the OP says just want to learn the very basics of Prolog! Please consider removing that tag. – Will Ness Mar 16 '12 at 20:19
  • @Will Ness: If you really want to discuss such issues, please use meta. – false Mar 16 '12 at 20:27

5 Answers5

7

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 = [_A]
;  Es = [_A,_B]
;  Es = [_A,_B,_C]
;  ... .

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).
false
  • 10,264
  • 13
  • 101
  • 209
  • Thanks! I'm going to have to look this over for a while and make sure I understand everything - still just figuring out the basics! - but I really appreciate the help :) – user1257768 Mar 13 '12 at 17:31
  • @user1257768: As a beginner, stick to lists and DCGs first. Don't do too much with `(is)/2`, `(>)/2` - or even `!/0`. You need to know too much about the actual execution to write correct programs. – false Mar 13 '12 at 18:55
  • 1
    **Very** confusing for a beginner. They "Just got introduced to prolog" and you throw **that** at them? – Will Ness Mar 16 '12 at 10:57
  • @user1257768 as a beginner, absolutely stick to lists, arithmetics, and cut, first. I recommend "The Art of Prolog". Stick to its order of chapters. When you get to difference lists, remember, it is just about maintaining the end-of-list pointer explicitly. Then, on to the [DCG](http://en.wikipedia.org/wiki/Definite_clause_grammar). – Will Ness Mar 16 '12 at 11:04
  • 3
    @Will Ness: The book you mention contains Chapter 8: Arithmetic, Chapter 11: Cuts and Negation. The preceding chapters do not use it. And neither "end-of-list pointer" nor difference lists are notions you need to understand DCGs. – false Mar 16 '12 at 14:32
  • YMMV. :) For me, DCG is an advanced concept above Prolog. Just as constraints, like `dif/2`, are. – Will Ness Mar 16 '12 at 19:58
  • 2
    @Will Ness: let continue at gusbro's answer! It is quite illustrative for the many things one tends to oversee when cuts and the like are present in a program. – false Mar 16 '12 at 20:05
  • @false as opposed to what, constraints?? – Will Ness Mar 16 '12 at 20:20
  • 2
    @Will Ness: As opposed to programs that do not use cuts and the like, such as if-then-else with the if-condition being a unification as in gusbro's program. – false Mar 16 '12 at 20:31
2

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.

  • +1: Your solution is the only alternate interpretation possible: You treat the list as is, as if the variables in the list would be all quantified. You use a cut, but with `(==)/2` as the guard. – false Mar 17 '12 at 22:54
1

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.

gusbro
  • 22,357
  • 35
  • 46
  • 1
    `X = b, plateau([a,a,X], 1, 2).` succeeds, but its generalization `plateau([a,a,X], 1, 2).` fails. – false Mar 13 '12 at 14:51
  • That is because it instantiates the free variable with a, thus it gives I=1, Len=3. The algorithm i wrote is greedy and will just unify variables with the previous item in the list. – gusbro Mar 13 '12 at 15:24
  • I'm not sure if I understand the problem pointed out by false? Probably just over my head... :) – user1257768 Mar 13 '12 at 17:34
  • What false says is that the solution I gave will instantiate unbounded variables in the input list with the previous item found in the list (allowing to get a larger sublist). It shouldn't be a problem if your input list does not have uninstantiated variables in it. – gusbro Mar 13 '12 at 17:58
  • 2
    @user1257768: The problem with gusbro's solution is that it is not a full relation. It works only if the list does not contain variables. But with variables, you do not get a generalized answer but something else. gusbro's solution would be much better, if it would produce an instantiation error in such a case. – false Mar 13 '12 at 19:02
  • I modified the first clause of plateau/6 to deal with the case of uninstantiated variables – gusbro Mar 13 '12 at 19:40
  • 1
    @gusbro: This never helps! If you cannot handle variables correctly, produce an error for a case you cannot decide. Consider: `plateau([A,B,C],I,Len).` You get answers for `I = 1` but not for `I = 2`! You could fix this as: `( (Item\=NItem;Item==NItem) -> true ; throw(error(instantiation_error,plateau/3)) )` – false Mar 13 '12 at 20:10
  • 1
    @gusbro: In the absence of constraints, `(A\=B;A==B)` is equivalent to the (non-standard) built-in `?=(A,B)`. – false Mar 13 '12 at 20:12
  • @false: but your solution also fails in the case [A,B,C]. It only yields one result I=1, Len=2 – gusbro Mar 14 '12 at 14:04
  • 1
    @gusbro: I disagree. There are 3 answers: Two with `Prefix = []` and one with `Prefix = [A]`. – false Mar 14 '12 at 14:59
  • @false why handle the vars in the list at all? The OP never said there will be any vars in the list. They just want to learn Prolog in its simplest; handling vars is extra-logical, is it not? `plateau([a,a,X], 1, 2).` fails because it ought to. *Plateau* is the *maximal* subsequence, and maximal subsequence of `[a,a,X]` is `[a,a,a]`. Of length 3. You read it differently, but this interpretation is just as valid. – Will Ness Mar 16 '12 at 11:18
  • 1
    @WillNess: 1st If you are using Prolog in its simplest (like in the beginning of St&Sh) you will never use an if-then-else as gusbro did above. Such an if-then-elese is (in this context) extra-logical. Using variables on the other hand is what we always do in Prolog. You don't have to state that. Also your other claim is false - see the next comment. – false Mar 16 '12 at 14:12
  • 1
    @WillNess: We may disagree about the very notion of a maximum. I.e., how variables are quantified in this case. However, regardless of the way how variables are quantified, `plateau([a,X,b,b], 2, 3).` should succeed but gusbro's definition fails here. – false Mar 16 '12 at 14:22
  • @false I should've said *meta*-logical. But anyway the question is **underspecified**. You interpretation is valid, but another would treat vars instantiation seqentially (like your clever use of `maplist(=(_),Es)` ), and see `X` as having to be instantiated to `a` once and for all, and so see your example as *must fail*. Equally validly. (my answer fails it too). – Will Ness Mar 16 '12 at 20:09
  • 1
    @Will Ness: I cannot see from the OP that `plateau([a,X,b,b], 2, 3).` should fail, nor any underspecification in that respect. And I tried to use the very arguments you used to justify that `plateau([a,a,X], 1, 2).` "ought to fail". So maybe we can only agree to disagree? – false Mar 16 '12 at 20:17
  • @false *linear* interpretation: "plateau" is a sequence of equal elts of maximal length; start from list's start; in `plateau([a,X,b,b], 2, 3)` must be X=a; **can't re-set X**; `plateau([a,X,b,b], 2, 3).` must fail -- `plateau([a,X,b,b],I,N).` must succeed twice. Your *non-linear* interpretation: start from indices - must re-instantiate X to different values: `plateau([a,X,b,b],I,N).` must succeed three times. Compare to: `maplist( =(_), Es)` is *linear* : anon var **is not re-set** for subsequent elts. – Will Ness Mar 16 '12 at 20:33
  • @false so of course each interpretation is valid. And that's what underspecified. (i.e. the presence of vars in list). -- to clarify the above comment: *linear*: succeed twice, with **same** value for `X` in both cases (i.e. `a`); *non-linear*: succeed three times, each time with its value for `X` (e.g. `a ; b ; c`). – Will Ness Mar 16 '12 at 20:37
  • @false (contd) and actually, why not 4 times, with `a ; b ; c ; d` or five, six etc. And so the *non-linear* interpretation unravels, it seems. – Will Ness Mar 16 '12 at 20:45
  • 1
    @WillNess: "start from list's start ... can't re-set X". I cannot relate this with what the OP stated, which was: "outputs all the sublists of the input list, where...". – false Mar 16 '12 at 20:47
  • @false "... where each sublist has length > 1 and cannot be extended to a larger sublist". So it all hinges on our interpretation of the word "cannot". You say, `plateau([a,X,b,b], I,N)` should succeed twice, with `X=a,I=1,N=2` and then `X=b,I=2,N=3`; I say after it succeeds once with `X=a` it "can't" have `X` assume `b` anymore and should suceed second time with `X=a,I=3,N=2`. A matter of taste. But note that OP clearly treats `I,N` as *output* variables: "It will also output the starting position ... ". And they *never* at all say there can *be* uninst'd vars in the list, at all. – Will Ness Mar 16 '12 at 21:08
  • @false IOW, "aa" and "bbb" are **not** two sublists of the **same** "input list" `[a,X,b,b]`. Right?? (*strange... thinking of observable value of* spin *right now, superpositions of states, etc...*) – Will Ness Mar 16 '12 at 21:14
1

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.
CapelliC
  • 59,646
  • 5
  • 47
  • 90
1

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))

Community
  • 1
  • 1
Will Ness
  • 70,110
  • 9
  • 98
  • 181