3

I'm trying to look through a list and count the number of times a given word appears. I've got this so far:

count_repetitions([_], [], 0).
count_repetitions([Word], [Word|Tail], Count):-
   count_repetitions([Word], Tail, X), 
   Count is X + 1.
count_repetitions([Word], [Z|Tail], Count):-
   Word \= Z, 
   count_repetitions([Word], Tail, Count).

So the query ?- count_repetitions([yes],[yes,and,yes,and,no], X). would give X = 2.

This appears to work. Now I need to write a predicate that outputs a list with the search word and the number of times it appears, in the form X = [(yes - 2)]. I'm completely stuck, any suggestions?

repeat
  • 18,496
  • 4
  • 54
  • 166
dlmb
  • 70
  • 2
  • 5

3 Answers3

8

This answer shows a logically pure way to do it. The following is based on .

:- use_module(library(clpfd)).

We define tcount/3 similarly to tfilter/3!

:- meta_predicate tcount(2,?,?).
tcount(P_2,Xs,N) :-
   N #>= 0,
   list_pred_tcount_(Xs,P_2,0,N).

:- meta_predicate list_pred_tcount_(?,2,?,?).
list_pred_tcount_([]    , _ ,N ,N).
list_pred_tcount_([X|Xs],P_2,N0,N) :-
   if_(call(P_2,X), (N1 is N0+1, N1 #=< N), N1 = N0),
   list_pred_tcount_(Xs,P_2,N1,N).

Now let's use tcount/3 in combination with (=)/3:

?- tcount(=(yes),[yes,and,yes,and,no],Count).
Count = 2.

Unlike the code presented by all other answers to this question, the code presented in this answer is monotone and remains logically sound even when using it with non-ground terms:

?- tcount(=(yes),[A,B,C,D],2).
      A=yes ,     B=yes , dif(C,yes), dif(D,yes)
;     A=yes , dif(B,yes),     C=yes , dif(D,yes)
;     A=yes , dif(B,yes), dif(C,yes),     D=yes
; dif(A,yes),     B=yes ,     C=yes , dif(D,yes)
; dif(A,yes),     B=yes , dif(C,yes),     D=yes
; dif(A,yes), dif(B,yes),     C=yes ,     D=yes
; false.

Let's try something even more general:

?- tcount(=(yes),[A,B,C,D],Count).
      A=yes ,     B=yes ,     C=yes ,     D=yes , Count = 4
;     A=yes ,     B=yes ,     C=yes , dif(D,yes), Count = 3
;     A=yes ,     B=yes , dif(C,yes),     D=yes , Count = 3
;     A=yes ,     B=yes , dif(C,yes), dif(D,yes), Count = 2
;     A=yes , dif(B,yes),     C=yes ,     D=yes , Count = 3
;     A=yes , dif(B,yes),     C=yes , dif(D,yes), Count = 2
;     A=yes , dif(B,yes), dif(C,yes),     D=yes , Count = 2
;     A=yes , dif(B,yes), dif(C,yes), dif(D,yes), Count = 1
; dif(A,yes),     B=yes ,     C=yes ,     D=yes , Count = 3
; dif(A,yes),     B=yes ,     C=yes , dif(D,yes), Count = 2
; dif(A,yes),     B=yes , dif(C,yes),     D=yes , Count = 2
; dif(A,yes),     B=yes , dif(C,yes), dif(D,yes), Count = 1
; dif(A,yes), dif(B,yes),     C=yes ,     D=yes , Count = 2
; dif(A,yes), dif(B,yes),     C=yes , dif(D,yes), Count = 1
; dif(A,yes), dif(B,yes), dif(C,yes),     D=yes , Count = 1
; dif(A,yes), dif(B,yes), dif(C,yes), dif(D,yes), Count = 0.

What about the following corner case?

?- tcount(_,_,-1).
false.

And how about utilizing tcount/3 as an alternative to length/2?

?- N in 1..3, length(Xs,N).
  N = 1, Xs = [_A]
; N = 2, Xs = [_A,_B]
; N = 3, Xs = [_A,_B,_C]
...                                      % does not terminate

?- use_module(library(lambda)).
true.

?- N in 1..3, tcount(\_^ =(true),Xs,N).
  N = 1, Xs = [_A]
; N = 2, Xs = [_A,_B]
; N = 3, Xs = [_A,_B,_C]
; false.                                 % terminates universally
repeat
  • 18,496
  • 4
  • 54
  • 166
  • 1
    Nice generalization, but the name. OK, it's about a noble count. Probably [Count von Count](https://www.google.com/search?q=count+count). – false May 01 '15 at 20:27
  • Minor ditch: `tcount(Pred_1, List, Count) :- list_pred_tcount(List, Pred_1, Count).` would be better on a WAM. And then, your counting could be improved by counting from 0 on! – false Jun 09 '15 at 11:02
  • 1
    Further ditch: `tcount(P_1, List, -1)` - should this really call `call(P_1,X)` at all? – false Jun 09 '15 at 12:10
  • @false: Guess the German name for "the count"... "Graf Zahl":) – repeat Aug 15 '15 at 18:14
  • Gróf Szám vs. Grófság – false Aug 18 '15 at 17:35
  • 1
    There is an error! It should be `:- meta_predicate tcount(2,?,?).` – false Jun 05 '17 at 21:02
  • 1
    @false. Thx 4 poing that out! Should be better now. – repeat Oct 19 '17 at 20:30
  • 1
    Bad for the nontermination of `N in 1..3, length(Xs,N).`. This is due to length/2 proposing larger and larger N but the constraint on the N prohibiting failing any attempt at instantiation past 3. There should be something in the constraint to tell length/2 that it will never find a solution that way. – David Tonhofer Feb 25 '21 at 22:00
  • @DavidTonhofer. I agree. There should. No program should depend on the non-termination of `N in 1..3, length(_,N), false`, so changing that behaviour is okay with me. But it also is somewhat ad-hoc-y, so the message it communicates is unclear. Right now, it's clear that old-school Prolog code like `library(lists)` behaves in this simple, but predictable way when used with finite-domain constraints. But what would reasonable expectations be with the extended `library(lists_X)` ? – repeat Mar 11 '21 at 08:55
4

You are there, already, it seems to me. You could simply wrap your predicate in another one saying:

word_repetitions(Word, List, [(Word-Count)]) :-
    count_repetitions(Word, List, Count).

Note that you don't need the parenthesis or the brackets around the Word-Count pair:

word_repetitions(Word, List, Word-Count) :-
    count_repetitions(Word, List, Count).

(but you can use them if you insist).

On your original predicate, renamed to reflect the differences:

list_word_reps([], Word, Word-0).
list_word_reps([W|Rest], Word, Word-Reps) :-
    list_word_reps(Rest, Word, Word-Reps0),
    (   W == Word
    ->  Reps is Reps0 + 1
    ;   Reps = Reps0
    ).

?- list_word_reps([yes,no,yes,no,maybe,yes], yes, X).
X = yes-3.

The reason why the list comes before the word is that the predicate then becomes deterministic. Same goes for using the if-then-else instead of two different clauses. You can put the answer in a list if you want to (just wrap the argument in brackets) but again, it is unnecessary.

  • Thanks for your solution Boris. Having the X = [yes - 2] was a bit of a typo on my part, it needn't be in brackets. Thanks again! – dlmb Dec 10 '13 at 12:50
2

library(aggregate) is often undervalued:

count(L, C) :-
    aggregate(set(W-N), aggregate(count, member(W, L), N), C).

yields

1 ?- count([a,b,a],C).
C = [a-2, b-1].

so, the simpler

count(W, L, W-N) :-
    aggregate(count, member(W, L), N).

yields

?- count(a, [a,b,a], C).
C = a-2.

being based on setof, aggregate/3 allows for finer control about the quantification of variables (i.e. which values get aggregated), but will fail if there is no solution, instead of yielding 0, as sometime is required.

aggregate_all/3, based on findall/3, would return 0 in such cases, but doesn't allows for quantification specifiers.

CapelliC
  • 59,646
  • 5
  • 47
  • 90