2

First piece of code:

count(X, [], 0).
count(X, [X|T], N) :-
  count(X, T, N1),
  N is N1 + 1.
count(X, [Y|T], N) :-
  X \= Y,
  count(X, T, N).

It shows the duplicate times by given element in the list. (There is no problem!) For example,

?- count(5, [1,5,5,3,3,3,4,2], X).
X = 2.

Second piece of code:

found(0, [], X).
found(N, [H|T], R):-
  count(R, [R|T], C),
  C == N.
found(N, [H|T], R):-
  count(R, [R|T], C),
  C \= N,
found(N, T, R).

It shows the element by given the duplicate times in a list. (But it is not perfect). For example,

?- found(2, [1,5,5,3,3,3,4], X).
X = 5. 

This is OK. However,

?- found(3, [1,5,5,3,3,3,4], X).
X = 5.

It is wrong! I have no idea about how to fix it.

repeat
  • 18,496
  • 4
  • 54
  • 166
Gold-One
  • 21
  • 2
  • 1
    You have a lot of singleton variable warnings. I bet if you replace them with `_` you will notice some problems--for instance, what happens to `H` in the second and third rules of `found/3`? – Daniel Lyons Apr 10 '14 at 16:17

2 Answers2

1

First things first! count/3 and found/3 is the same.

We define count/3 using , tcount/3 and reified term equality (=)/3:

:- use_module(library(clpfd)).

count(E,Xs,N) :-
   tcount(=(E),Xs,N).

Q: "What is the number of occurrences N of e in [a,e,e,c,c,c,d,b]?"

?- count(e,[a,e,e,c,c,c,d,b],N).
N = 2.

Q: "Which X occurs more than three times in [a,e,e,c,c,c,d,b]?"

?- N #> 3, count(X,[a,e,e,c,c,c,d,b],N).
false.

Q: "Which X occurs exactly three times in [a,e,e,c,c,c,d,b]?"

?- count(X,[a,e,e,c,c,c,d,b],3). 
  X = c
; false.

Q: "Which X occurs exactly twice in [a,e,e,c,c,c,d,b]?"

?- count(X,[a,e,e,c,c,c,d,b],2).
  X = e
; false.

Q: "Which X occurs exactly once in [a,e,e,c,c,c,d,b]?"

?- count(X,[a,e,e,c,c,c,d,b],1).
  X = a
; X = d
; X = b
; false.

Q: "Which X occurs exactly zero times in [a,e,e,c,c,c,d,b]?"

?- count(X,[a,e,e,c,c,c,d,b],0).
dif(X,a), dif(X,b), dif(X,c), dif(X,d), dif(X,e).
Community
  • 1
  • 1
repeat
  • 18,496
  • 4
  • 54
  • 166
0

You say there is no problem with count/3 but I beg to differ:

?- count(X, [1,5,5,3,3,3,4,2], Z).
X = Z, Z = 1 ;
false.

What I'd like to see here is:

X = Z, Z = 1 ;
X = 5, Z = 2 ;
X = Z, Z = 3 ;
X = 4, Z = 1 ;
X = 2, Z = 1 ;
false.

It just seems to me that count/3 should be able to come up list items other than the first one. Which, indeed, it can only come up with because the second rule has something to say about the head of the list. Your singleton warning comes up because of the first rule, which would be better stated as:

count(_, [], 0).

What you're really saying with that rule is, "Whatever you're looking for, if the list is empty, the count of that thing is 0." I can think of other ways to restate this predicate that generate for the first argument, but none of them retain this very pleasing property. I suspect @false will amble along at some point and tell us both why we're both wrong. But here's the way I would be inclined to state count/3:

count(Item, List, 0) :- \+ memberchk(Item, List).
count(Item, List, N) :-
    % get us each unique item, one by one (or confirm that X is in the list)
    sort(List, Sorted), member(Item, Sorted),

    % make a list of the items that match
    bagof(Item, member(Item, List), Occurrences),

    % count them
    length(Occurrences, N).

This is odd and awkward and there is probably a better way to do it, but it fulfills both our requirements:

?- count(X, [1,5,5,3,3,3,4,2], Z).
X = Z, Z = 1 ;
X = 2,
Z = 1 ;
X = Z, Z = 3 ;
X = 4,
Z = 1 ;
X = 5,
Z = 2.

?- count(0, [1,5,5,3,3,3,4,2], Z).
Z = 0 ;
false.

?- count(5, [1,5,5,3,3,3,4,2], Z).
Z = 2.

Now let's turn our attention to found/3. First let's change the code to address the singleton errors so we can see where the problems may lie:

found(0, [], _).
found(N, [_|T], R):-
  count(R, [R|T], C),
  C == N.
found(N, [_|T], R):-
  count(R, [R|T], C),
  C \= N,
  found(N, T, R).

Immediately we see that in the second and third rules, we're insinuating an R on the front of the list. Probably in both cases we want to keep H and pass it along or do something tricky. In fact, it would probably be safer to just use L, because we shouldn't have to do anything fancy with the list—the count/3 procedure should be sufficient. On inspection, I have no idea what you're trying to accomplish with the third rule. In fact, we can delete it altogether and we arrive at the following definition:

found(0, [], _).
found(N, L, R):-
  count(R, L, C),
  C == N.

It works for your two use cases, but guess what? We don't need found/3 at all, because count/3 can do them now!

?- count(X, [1,5,5,3,3,3,4], 3).
X = 3 ;
false.

?- count(X, [1,5,5,3,3,3,4], 2).
X = 5.

These are literally asking questions like "What is the element that occurs 2 times?" Prolog eliminated the need for the whole other predicate. You could definite it trivially now, with the following simple definition:

found(X, Y, Z) :- count(Z, Y, X).

One parting comment: you would probably find your code a lot easier to debug if you use real, non-single-letter variable names. Look at my definition of count/3. It's a little bigger, but it's a lot easier to follow. I often use [H|T] or [X|Xs] in my own code, but in general, a proliferation of X, Y, Z and so forth makes it very hard to follow while reading the code, and reading the code is exceptionally important in declarative languages where most of the flow is really about which variables are used where.

Daniel Lyons
  • 22,421
  • 2
  • 50
  • 77