Intersection of two lists of variables - prolog

How to define in ISO Prolog a (meta-logical) predicate for the intersection of two lists of variables that runs in linear time? The variables may appear in any determined order. No implementation dependent property like the "age" of variables must influence the outcome.
In analogy to library(ordsets), let's call the relation varset_intersection(As, Bs, As_cap_Bs).
?- varset_intersection([A,B], [C,D], []).
true.
?-varset_intersection([A,B], [B,A], []).
false.
?- varset_intersection([A,B,C], [C,A,D], Inter).
Inter = [A,C].
or
Inter = [C,A].
?- varset_intersection([A,B],[A,B],[A,C]).
B = C
or
A = B, A = C
?- varset_intersection([A,B,C],[A,B],[A,C]).
idem
That is, the third argument is an output argument, that unifies with the intersection of the first two arguments.
See this list of the built-ins from the current ISO standard (ISO/IEC 13211-1:1995 including Cor.2).
(Note, that I did answer this question in the course of another one several years ago. However, it remains hidden and invisible to Google.)

If term_variables/2 works in a time linear with the size of its first argument, then this might work:
varset_intersection(As, Bs, As_cap_Bs):-
term_variables([As, Bs], As_and_Bs),
term_variables(As, SetAs),
append(SetAs, OnlyBs, As_and_Bs),
term_variables([OnlyBs, Bs], SetBs),
append(OnlyBs, As_cap_Bs, SetBs).
Each common variable appears only once in the result list no matter how many times it appears in the two given lists.
?- varset_intersection2([A,_C,A,A,A], [A,_B,A,A,A], L).
L = [A].
Also, it might give strange results as in this case:
?- varset_intersection([A,_X,B,C], [B,C,_Y,A], [C, A, B]).
A = B, B = C.
(permutation/2 might help here).

If copy_term/2 uses linear time, I believe the following works:
varset_intersection(As, Bs, Cs) :-
copy_term(As-Bs, CopyAs-CopyBs),
ground_list(CopyAs),
select_grounded(CopyBs, Bs, Cs).
ground_list([]).
ground_list([a|Xs]) :-
ground_list(Xs).
select_grounded([], [], []).
select_grounded([X|Xs], [_|Bs], Cs) :-
var(X),
!,
select_grounded(Xs, Bs, Cs).
select_grounded([_|Xs], [B|Bs], [B|Cs]) :-
select_grounded(Xs, Bs, Cs).
The idea is to copy both lists in one call to copy_term/2 to preserve shared variables between them, then ground the variables of the first copy, then pick out the original variables of the second list corresponding to the grounded positions of the second copy.

If unify_with_occurs_check(Var, ListOfVars) fails or succeeds in constant time, this implementation should yield answers in linear time:
filter_vars([], _, Acc, Acc).
filter_vars([A|As], Bs, Acc, As_cap_Bs):-
(
\+ unify_with_occurs_check(A, Bs)
->
filter_vars(As, Bs, [A|Acc], As_cap_Bs)
;
filter_vars(As, Bs, Acc, As_cap_Bs)
).
varset_intersection(As, Bs, As_cap_Bs):-
filter_vars(As, Bs, [], Inter),
permutation(Inter, As_cap_Bs).
This implementation has problems when given lists contain duplicates:
?- varset_intersection1([A,A,A,A,B], [B,A], L).
L = [B, A, A, A, A] ;
?- varset_intersection1([B,A], [A,A,A,A,B], L).
L = [A, B] ;
Edited : changed bagof/3 to a manually written filter thanks to observation by #false in comments below.

A possible solution is to use a Bloom filter. In case of collision, the result might be wrong, but functions with better collision resistance exist. Here is an implementation that uses a single hash function.
sum_codes([], _, Sum, Sum).
sum_codes([Head|Tail], K, Acc,Sum):-
Acc1 is Head * (256 ** K) + Acc,
K1 is (K + 1) mod 4,
sum_codes(Tail, K1, Acc1, Sum).
hash_func(Var, HashValue):-
with_output_to(atom(A), write(Var)),
atom_codes(A, Codes),
sum_codes(Codes, 0, 0, Sum),
HashValue is Sum mod 1024.
add_to_bitarray(Var, BAIn, BAOut):-
hash_func(Var, HashValue),
BAOut is BAIn \/ (1 << HashValue).
bitarray_contains(BA, Var):-
hash_func(Var, HashValue),
R is BA /\ (1 << HashValue),
R > 0.
varset_intersection(As, Bs, As_cap_Bs):-
foldl(add_to_bitarray, As, 0, BA),
include(bitarray_contains(BA), Bs, As_cap_Bs).
I know that foldl/4 and include/3 are not ISO, but their implementation is easy.

Related

(SWI)Prolog: Order of sub-goals

I have two, slightly different, implementations of a predicate, unique_element/2, in Prolog. The predicate succeeds when given an element X and a list L, the element X appears only once in the list. Below are the implementations and the results:
Implementation 1:
%%% unique_element/2
unique_element(Elem, [Elem|T]) :-
not(member(Elem, T)).
unique_element(Elem, [H|T]) :-
member(Elem, T),
H\==Elem,
unique_element(Elem, T),
!.
Results:
?- unique_element(X, [a, a, b, c, c, b]).
false.
?- unique_element(X, [a, b, c, c, b, d]).
X = a ;
X = d.
Implementation 2:
%%% unique_element/2
unique_element(Elem, [Elem|T]) :-
not(member(Elem, T)).
unique_element(Elem, [H|T]) :-
H\==Elem,
member(Elem, T),
unique_element(Elem, T),
!.
In case you didn't notice at first sight: H\==Elem and member(Elem, T) are flipped on the 2nd impl, rule 2.
Results:
?- unique_element(X, [a, a, b, c, c, b]).
X = a.
?- unique_element(X, [a, b, c, c, b, d]).
X = a ;
X = d.
Question: How does the order, in this case, affect the result? I realize that the order of the rules/facts/etc matters. The two specific rules that are flipped though, don't seem to be "connected" or affect each other somehow (e.g. a cut in the wrong place/order).
Note: We are talking about SWI-Prolog here.
Note 2: I am aware of, probably different and better implementations. My question here is about the order of sub-goals being changed.
H\==Elem is testing for syntactic inequality at the point in time when the goal is executed. But later unification might make variables identical:
?- H\==Elem, H = Elem.
H = Elem.
?- H\==Elem, H = Elem, H\==Elem.
false.
So here we test if they are (syntactically) different, and then they are unified nevertheless and thus are no longer different. It is thus just a temporary test.
The goal member(Elem, T) on the other hand is true if that Elem is actually an element of T. Consider:
?- member(Elem, [X]).
Elem = X.
Which can be read as
(When) does it hold that Elem is an element of the list [X]?
and the answer is
It holds under certain circumstances, namely when Elem = X.
If you now mix those different kinds of goals in your programs you get odd results that can only explained by inspecting your program in detail.
As a beginner, it is best to stick to the pure parts of Prolog only. In your case:
use dif/2 in place of \==
do not use cuts - in your case it limits the number of answers to two. As in
unique_element(X, [a,b,c])
do not use not/1 nor (\+)/1. It produces even more incorrectness. Consider unique_element(a,[a,X]),X=b. which incorrectly fails while X=b,unique_element(a,[a,X]) correctly succeeds.
Here is a directly purified version of your program. There is still room for improvement!
non_member(_X, []).
non_member(X, [E|Es]) :-
dif(X, E),
non_member(X, Es).
unique_element(Elem, [Elem|T]) :-
non_member(Elem, T).
unique_element(Elem, [H|T]) :-
dif(H,Elem),
% member(Elem, T), % makes unique_element(a,[b,a,a|Xs]) loop
unique_element(Elem, T).
?- unique_element(a,[a,X]).
dif(X, a)
; false. % superfluous
?- unique_element(X,[E1,E2,E3]).
X = E1, dif(E1, E3), dif(E1, E2)
; X = E2, dif(E2, E3), dif(E1, E2)
; X = E3, dif(E2, E3), dif(E1, E3)
; false.
Note how the last query reads?
When is X a unique element of (any) list [E1,E2,E3]?
The answer is threefold. Considering one element after the other:
X is E1 but only if it is different to E2 and E3
etc.
TL;DR: Read the documentation and figure out why:
?- X = a, X \== a.
false.
?- X \== a, X = a.
X = a.
I wonder why you stop so close from figuring it out yourself ;-)
There are too many ways to compare things in Prolog. At the very least, you have unification, which sometimes can compare, and sometimes does more; than you have equvalence, and its negation, the one you are using. So what does it do:
?- a \== b. % two different ground terms
true.
?- a \== a. % the same ground term
false.
Now it gets interesting:
?- X \== a. % a free variable and a ground term
true.
?- X \== X. % the same free variable
false.
?- X \== Y. % two different free variables
true.
I would suggest that you do the following: figure out how member/2 does its thing (does it use unification? equivalence? something else?) then replace whatever member/2 is using in all the examples above and see if the results are any different.
And since you are trying to make sure that things are different, try out what dif/2 does. As in:
?- dif(a, b).
or
?- dif(X, X).
or
?- dif(X, a).
and so on.
See also this question and answers: I think the answers are relevant to your question.
Hope that helps.
Here is another possibility do define unique_element/2 using if_/3 and maplist/2:
:- use_module(library(apply)).
unique_element(Y,[X|Xs]) :-
if_(Y=X,maplist(dif(Y),Xs),unique_element(Y,Xs)).
In contrast to #user27815's very elegant solution (+s(0)) this version does not build on clpfd (used by tcount/3). The example queries given by the OP work as expected:
?- unique_element(a,[a, a, b, c, c, b]).
no
?- unique_element(X,[a, b, c, c, b, d]).
X = a ? ;
X = d ? ;
no
The example provided by #false now succeeds without leaving a superfluous choicepoint:
?- unique_element(a,[a,X]).
dif(a,X)
The other more general query yields the same results:
?- unique_element(X,[E1,E2,E3]).
E1 = X,
dif(X,E3),
dif(X,E2) ? ;
E2 = X,
dif(X,E3),
dif(X,E1) ? ;
E3 = X,
dif(X,E2),
dif(X,E1) ? ;
no
Can you not define unique_element like tcount Prolog - count repetitions in list
unique_element(X, List):- tcount(=(X),List,1).

List indexes on a recursive program?

I've been searching for something that might help me with my problem all over the internet but I haven't been able to make any progress. I'm new to logic programming and English is not my first language so apologize for any mistake.
Basically I want to implement this prolog program: discord/3 which has arguments L1, L2 lists and P where P are the indexes of the lists where L1[P] != L2[P] (in Java). In case of different lengths, the not paired indexes just fail. Mode is (+,+,-) nondet.
I got down the basic case but I can't seem to wrap my head around on how to define P in the recursive call.
discord(_X,[],_Y) :-
fail.
discord([H1|T1],[H1|T2],Y) :-
???
discord(T1,T2,Z).
discord([_|T1],[_|T2],Y) :-
???
discord(T1,T2,Z).
The two clauses above are what I came up to but I have no idea on how to represent Y - and Z - so that the function actually remembers the length of the original list. I've been thinking about using nth/3 with eventually an assert but I'm not sure where to place them in the program.
I'm sure there has to be an easier solution although. Thanks in advance!
You can approach this in two ways. First, the more declarative way would be to enumerate the indexed elements of both lists with nth1/3 and use dif/2 to ensure that the two elements are different:
?- L1 = [a,b,c,d],
L2 = [x,b,y,d],
dif(X, Y),
nth1(P, L1, X),
nth1(P, L2, Y).
X = a, Y = x, P = 1 ;
X = c, Y = y, P = 3 ;
false.
You could also attempt to go through both list at the same time and keep a counter:
discord(L1, L2, P) :-
discord(L1, L2, 1, P).
discord([X|_], [Y|_], P, P) :-
dif(X, Y).
discord([_|Xs], [_|Ys], N, P) :-
succ(N, N1),
discord(Xs, Ys, N1, P).
Then, from the top level:
?- discord([a,b,c,d], [a,x,c,y], Ps).
Ps = 2 ;
Ps = 4 ;
false.

Append list of lists elements in Prolog

I'm learning Prolog for about a week, so I'm a newbie.
I'm trying to do a function, that appends, the elements of a list of lists.
So the input would be: [ [[a,b,c],[g,h,i]], [[j,k,l],[m,n,o]], [[s,t,u],[v,w,x]] ].
And the output would be : [ [a,b,c,j,k,l,s,t,u], [g,h,i,m,n,o,v,w,x] ].
Or
Input: [ [[a,b], [c,d]], [[e,f], [g,h]], [[i,j],[k,l]] ].
Output: [ [a,b,e,f,i,j], [c,d,g,h,k,l] ].
It would be important, that it has to work with a lot of elements, not only 3.
I wrote this, but it only works with 2 elements, so i can only do it, with pairs.
merge([],[],[]).
merge(L1,[],L1).
merge([H1|T1],[H2|T2],LL):-
append(H1, H2, HE),
merge(T1,T2,TE),
append([HE], TE, LL).
If I understand your question correctly...
First, if you know that your input has exactly two levels of nesting in it, and if your Prolog had higher-order predicates for mapping and for folding, and if you could compose them, you could simply write:
merge_foldl([], []).
merge_foldl([X|Xs], R) :-
reverse([X|Xs], [Y|Ys]),
foldl(maplist(append), Ys, Y, R).
This works as expected for SWI-Prolog.
Here it is with your two examples:
?- merge_foldl([ [[a,b,c],[g,h,i]], [[j,k,l],[m,n,o]], [[s,t,u],[v,w,x]] ], R).
R = [[a, b, c, j, k, l, s, t, u], [g, h, i, m, n, o, v, w, x]].
?- merge_foldl([ [[a,b], [c,d], [e,f]], [[g,h], [i,j], [k,l]] ], R).
R = [[a, b, g, h], [c, d, i, j], [e, f, k, l]].
If you don't have access to neither foldr nor foldl, you would have to hardcode the folding:
merge([], []).
merge([X|Xs], Result) :-
merge_maplist(Xs, X, Result).
merge_maplist([], Result, Result).
This is not all, but it says that if you are at the end of the list of lists, the last element is the result.
Now you have to define the step where you append to the front of each sublist. This is easier with maplist:
merge_maplist([X|Xs], Prev, Result) :-
merge_maplist(Xs, X, Result0),
maplist(append, Prev, Result0, Result).
Note that here we are "emulating" a right fold by using a non-tail-recursive definition: we are doing the appending in reverse, after the recursive step. For a tail-recursive definition (identical to hard-coded left fold), you would have to reverse the original list first!
So you keep on peeling off one list of lists from your input until you are done. Then, you use maplist to apply append/3 to each pair of lists from the previous element and the result so far, to get the final result.
If you don't have access to maplist either, you'd have to hardcode the mapping as well. For the three arguments that append/3 takes:
map_append([], [], []).
map_append([X|Xs], [Y|Ys], [Z|Zs]) :-
append(X, Y, Z),
map_append(Xs, Ys, Zs).
and your merge/2 and merge_/3 become:
merge([], []).
merge([X|Xs], Result) :-
merge_(Xs, X, Result).
merge_([], Result, Result).
merge_([X|Xs], Prev, Result) :-
merge_(Xs, X, Result0),
map_append(Prev, Result0, Result).
This is a lot of code for something that can be solved quite nicely if you have higher-order predicates.

Count occurrences Prolog

I'm new in Prolog and trying to do some programming with Lists
I want to do this :
?- count_occurrences([a,b,c,a,b,c,d], X).
X = [[d, 1], [c, 2], [b, 2], [a, 2]].
and this is my code I know it's not complete but I'm trying:
count_occurrences([],[]).
count_occurrences([X|Y],A):-
occurrences([X|Y],X,N).
occurrences([],_,0).
occurrences([X|Y],X,N):- occurrences(Y,X,W), N is W + 1.
occurrences([X|Y],Z,N):- occurrences(Y,Z,N), X\=Z.
My code is wrong so i need some hits or help plz..
Here's my solution using bagof/3 and findall/3:
count_occurrences(List, Occ):-
findall([X,L], (bagof(true,member(X,List),Xs), length(Xs,L)), Occ).
An example
?- count_occurrences([a,b,c,b,e,d,a,b,a], Occ).
Occ = [[a, 3], [b, 3], [c, 1], [d, 1], [e, 1]].
How it works
bagof(true,member(X,List),Xs) is satisfied for each distinct element of the list X with Xs being a list with its length equal to the number of occurrences of X in List:
?- bagof(true,member(X,[a,b,c,b,e,d,a,b,a]),Xs).
X = a,
Xs = [true, true, true] ;
X = b,
Xs = [true, true, true] ;
X = c,
Xs = [true] ;
X = d,
Xs = [true] ;
X = e,
Xs = [true].
The outer findall/3 collects element X and the length of the associated list Xs in a list that represents the solution.
Edit I: the original answer was improved thanks to suggestions from CapelliC and Boris.
Edit II: setof/3 can be used instead of findall/3 if there are free variables in the given list. The problem with setof/3 is that for an empty list it will fail, hence a special clause must be introduced.
count_occurrences([],[]).
count_occurrences(List, Occ):-
setof([X,L], Xs^(bagof(a,member(X,List),Xs), length(Xs,L)), Occ).
Note that so far all proposals have difficulties with lists that contain also variables. Think of the case:
?- count_occurrences([a,X], D).
There should be two different answers.
X = a, D = [a-2]
; dif(X, a), D = [a-1,X-1].
The first answer means: the list [a,a] contains a twice, and thus D = [a-2]. The second answer covers all terms X that are different to a, for those, we have one occurrence of a and one occurrence of that other term. Note that this second answer includes an infinity of possible solutions including X = b or X = c or whatever else you wish.
And if an implementation is unable to produce these answers, an instantiation error should protect the programmer from further damage. Something along:
count_occurrences(Xs, D) :-
( ground(Xs) -> true ; throw(error(instantiation_error,_)) ),
... .
Ideally, a Prolog predicate is defined as a pure relation, like this one. But often, pure definitions are quite inefficient.
Here is a version that is pure and efficient. Efficient in the sense that it does not leave open any unnecessary choice points. I took #dasblinkenlight's definition as source of inspiration.
Ideally, such definitions use some form of if-then-else. However, the traditional (;)/2 written
( If_0 -> Then_0 ; Else_0 )
is an inherently non-monotonic construct. I will use a monotonic counterpart
if_( If_1, Then_0, Else_0)
instead. The major difference is the condition. The traditional control constructs relies upon the success or failure of If_0 which destroys all purity. If you write ( X = Y -> Then_0 ; Else_0 ) the variables X and Y are unified and at that very point in time the final decision is made whether to go for Then_0 or Else_0. What, if the variables are not sufficiently instantiated? Well, then we have bad luck and get some random result by insisting on Then_0 only.
Contrast this to if_( If_1, Then_0, Else_0). Here, the first argument must be some goal that will describe in its last argument whether Then_0 or Else_0 is the case. And should the goal be undecided, it can opt for both.
count_occurrences(Xs, D) :-
foldl(el_dict, Xs, [], D).
el_dict(K, [], [K-1]).
el_dict(K, [KV0|KVs0], [KV|KVs]) :-
KV0 = K0-V0,
if_( K = K0,
( KV = K-V1, V1 is V0+1, KVs0 = KVs ),
( KV = KV0, el_dict(K, KVs0, KVs ) ) ).
=(X, Y, R) :-
equal_truth(X, Y, R).
This definition requires the following auxiliary definitions:
if_/3, equal_truth/3, foldl/4.
If you use SWI-Prolog, you can do :
:- use_module(library(lambda)).
count_occurrences(L, R) :-
foldl(\X^Y^Z^(member([X,N], Y)
-> N1 is N+1,
select([X,N], Y, [X,N1], Z)
; Z = [[X,1] | Y]),
L, [], R).
One thing that should make solving the problem easier would be to design a helper predicate to increment the count.
Imagine a predicate that takes a list of pairs [SomeAtom,Count] and an atom whose count needs to be incremented, and produces a list that has the incremented count, or [SomeAtom,1] for the first occurrence of the atom. This predicate is easy to design:
increment([], E, [[E,1]]).
increment([[H,C]|T], H, [[H,CplusOne]|T]) :-
CplusOne is C + 1.
increment([[H,C]|T], E, [[H,C]|R]) :-
H \= E,
increment(T, E, R).
The first clause serves as the base case, when we add the first occurrence. The second clause serves as another base case when the head element matches the desired element. The last case is the recursive call for the situation when the head element does not match the desired element.
With this predicate in hand, writing count_occ becomes really easy:
count_occ([], []).
count_occ([H|T], R) :-
count_occ(T, Temp),
increment(Temp, H, R).
This is Prolog's run-of-the-mill recursive predicate, with a trivial base clause and a recursive call that processes the tail, and then uses increment to account for the head element of the list.
Demo.
You have gotten answers. Prolog is a language which often offers multiple "correct" ways to approach a problem. It is not clear from your answer if you insist on any sort of order in your answers. So, ignoring order, one way to do it would be:
Sort the list using a stable sort (one that does not drop duplicates)
Apply a run-length encoding on the sorted list
The main virtue of this approach is that it deconstructs your problem to two well-defined (and solved) sub-problems.
The first is easy: msort(List, Sorted)
The second one is a bit more involved, but still straight forward if you want the predicate to only work one way, that is, List --> Encoding. One possibility (quite explicit):
list_to_rle([], []).
list_to_rle([X|Xs], RLE) :-
list_to_rle_1(Xs, [[X, 1]], RLE).
list_to_rle_1([], RLE, RLE).
list_to_rle_1([X|Xs], [[Y, N]|Rest], RLE) :-
( dif(X, Y)
-> list_to_rle_1(Xs, [[X, 1],[Y, N]|Rest], RLE)
; succ(N, N1),
list_to_rle_1(Xs, [[X, N1]|Rest], RLE)
).
So now, from the top level:
?- msort([a,b,c,a,b,c,d], Sorted), list_to_rle(Sorted, RLE).
Sorted = [a, a, b, b, c, c, d],
RLE = [[d, 1], [c, 2], [b, 2], [a, 2]].
On a side note, it is almost always better to prefer "pairs", as in X-N, instead of lists with two elements exactly, as in [X, N]. Furthermore, you should keep the original order of the elements in the list, if you want to be correct. From this answer:
rle([], []).
rle([First|Rest],Encoded):-
rle_1(Rest, First, 1, Encoded).
rle_1([], Last, N, [Last-N]).
rle_1([H|T], Prev, N, Encoded) :-
( dif(H, Prev)
-> Encoded = [Prev-N|Rest],
rle_1(T, H, 1, Rest)
; succ(N, N1),
rle_1(T, H, N1, Encoded)
).
Why is it better?
we got rid of 4 pairs of unnecessary brackets in the code
we got rid of clutter in the reported solution
we got rid of a whole lot of unnecessary nested terms: compare .(a, .(1, [])) to -(a, 1)
we made the intention of the program clearer to the reader (this is the conventional way to represent pairs in Prolog)
From the top level:
?- msort([a,b,c,a,b,c,d], Sorted), rle(Sorted, RLE).
Sorted = [a, a, b, b, c, c, d],
RLE = [a-2, b-2, c-2, d-1].
The presented run-length encoder is very explicit in its definition, which has of course its pros and cons. See this answer for a much more succinct way of doing it.
refining joel76 answer:
count_occurrences(L, R) :-
foldl(\X^Y^Z^(select([X,N], Y, [X,N1], Z)
-> N1 is N+1
; Z = [[X,1] | Y]),
L, [], R).

Python counter in Prolog

In Python you can do
>>> import from collections counter
>>> Counter(['a','b','b','c'])
>>> Counter({'b': 2, 'a': 1, 'c': 1})
Is there something similar in Prolog? Like so:
counter([a,b,b,c],S).
S=[a/1,b/2,c/1].
This is my implementation:
counter([],List,Counts,Counts).
counter([H|T],List,Counts0,[H/N|Counts]):-
findall(H, member(H,List), S),
length(S,N),
counter(T,List,Counts0,Counts).
counter(List,Counts):-
list_to_set(List,Set),
counter(Set,List,[],Counts).
It's rather verbose, so I wondered if there was a builtin predicate or a more terse implementation.
There is no builtin predicate, here is another way to do that :
counter([X], [X/1]).
counter([H | T], R) :-
counter(T, R1),
( select(H/V, R1, R2)
-> V1 is V+1,
R = [H/V1 | R2]
; R = [H/1 | R1]).
I like #joel76's solution. I will add a few more variations on the theme.
VARIATION I
Here's another simple approach, which sorts the list first:
counter(L, C) :-
msort(L, S), % Use 'msort' instead of 'sort' to preserve dups
counter(S, 1, C).
counter([X], A, [X-A]).
counter([X,X|T], A, C) :-
A1 is A + 1,
counter([X|T], A1, C).
counter([X,Y|T], A, [X-A|C]) :-
X \= Y,
counter([Y|T], 1, C).
Quick trial:
| ?- counter([a,b,b,c], S).
S = [a-1,b-2,c-1] ?
yes
This will fail on counter([], C). but you can simply include the clause counter([], []). if you want it to succeed. It doesn't maintain the initial order of appearance of the elements (it's unclear whether this is a requirement). This implementation is fairly efficient and is tail recursive, and it will work as long as the first argument is instantiated.
VARIATION II
This version will maintain order of appearance of elements, and it succeeds on counter([], []).. It's also tail recursive:
counter(L, C) :-
length(L, N),
counter(L, N, C).
counter([H|T], L, [H-C|CT]) :-
delete(T, H, T1), % Remove all the H's
length(T1, L1), % Length of list without the H's
C is L - L1, % Count is the difference in lengths
counter(T1, L1, CT). % Recursively do the sublist
counter([], _, []).
With some results:
| ?- counter([a,b,a,a,b,c], L).
L = [a-3,b-2,c-1]
yes
| ?- counter([], L).
L = []
yes
VARIATION III
This one uses a helper which isn't tail recursive, but it preserves the original order of elements, is fairly concise, and I think more efficient.
counter([X|T], [X-C|CT]) :-
remove_and_count(X, [X|T], C, L), % Remove and count X from the list
counter(L, CT). % Count remaining elements
counter([], []).
% Remove all (C) instances of X from L leaving R
remove_and_count(X, L, C, R) :-
select(X, L, L1), !, % Cut to prevent backtrack to other clause
remove_and_count(X, L1, C1, R),
C is C1 + 1.
remove_and_count(_, L, 0, L).
This implementation will work as long as the first argument to counter is instantiated.
SIDEBAR
In the above predicates, I used the Element-Count pattern rather than Element/Count since some Prolog interpreters, SWI in particular, offer a number of predicates that know how to operate on associative lists of Key-Value pairs (see SWI library(pairs) and ISO predicate keysort/2).
I also like #joel76 solution (and #mbratch suggestions, also). Here I'm just to note that library(aggregate), if available, has a count aggregate operation, that can be used with the ISO builtin setof/3:
counter(L, Cs) :-
setof(K-N, (member(K, L), aggregate(count, member(K, L), N)), Cs).
yields
?- counter([a,b,b,c], L).
L = [a-1, b-2, c-1].
If the selection operation was more complex, a nice way to avoid textually repeating the code could be
counter(L, Cs) :-
P = member(K, L),
setof(K-N, (P, aggregate(count, P, N)), Cs).
edit
Since I'm assuming library(aggregate) available, could be better to task it the set construction also:
counter(L, Cs) :-
P = member(E,L), aggregate(set(E-C), (P, aggregate(count,P,C)), Cs).

Resources