3

I have a list of elements which contains the number of friends a person has.

[friends(mike, 4), friends(joe, 3), friends(mike, 1), friends(mike, 2)]

I want to compress this list and obtain the following

[friends(mike, 7), friend(joe, 3)]

I created member, and delete first appearance.

member(E, [E|_]).
member(E, [_|Y]) :- 
    member(E, Y).

delete_first([], _, []).
delete_first([X|Y], X, Y).
delete_first([X|Y], E, [X|L]) :- 
    X \= E, 
    delete_first(Y, E, L).

compress([], []).
compress([friends(P, C)|R], S) :- 
    member(friends(P, X), R), 
    delete_first(R, friends(P, X), E), 
    N is C + X, 
    compress([friends(P, N)|E], S).
compress([friends(P, C)|R], [friends(P, C)|S]) :- 
    not(member(friends(P, _), R)), 
    compress(R, S).

I'm getting my answers right but Prolog returns the same answer several times. Why is that happening?

Example:

?- compress([friends(mike, 4), friends(joe, 3), friends(mike, 1), 
             friends(mike, 2), friends(joe,4), friends(mike, 3)],X).
X = [friends(mike, 10), friends(joe, 7)] ;
X = [friends(mike, 10), friends(joe, 7)] ;
X = [friends(mike, 10), friends(joe, 7)] ;
X = [friends(mike, 10), friends(joe, 7)] ;
X = [friends(mike, 10), friends(joe, 7)] ;
X = [friends(mike, 10), friends(joe, 7)] ;
false.
repeat
  • 18,496
  • 4
  • 54
  • 166
AwesomeGuy
  • 537
  • 1
  • 6
  • 17

4 Answers4

5

Another way is to use aggregate/3 (which works with SWI-Prolog) :

compress(In, Out) :-
     aggregate(set(friends(P,S)), aggregate(sum(X), member(friends(P,X), In), S), Out).

Result :

?- compress([friends(mike, 4), friends(joe, 3), friends(mike, 1),friends(mike, 2), friends(joe,4), friends(mike, 3)],X).
X = [friends(joe, 7), friends(mike, 10)].
joel76
  • 5,565
  • 1
  • 18
  • 22
  • +1: library(aggregate) is so often unrepresented... should be the weapon of choice, given that people have plenty of confidence in aggregating SQL operators – CapelliC Feb 10 '19 at 19:41
3

Sorry for not really answering your question and giving you an alternative solution instead.

What you are doing is too round-about without any obvious benefits (but please correct me if I am wrong).

An idiomatic approach would be to sort without removing duplicates using msort/2. This will bring entries you need to aggregate next to each other. Then it is easier to do the math.

Even easier if you also used group_pairs_by_key/2:

friends_compressed(L, C) :-
    maplist(friends_pair, L, Pairs),
    msort(Pairs, Sorted),
    group_pairs_by_key(Sorted, Grouped),
    maplist(counts_sum, Grouped, Summed),
    maplist(friends_pair, C, Summed).

friends_pair(friends(Name, Number), Name-Number).

counts_sum(X-Counts, X-Sum) :-
    sum_list(Counts, Sum).

Most of this code is converting from friends(Name, Count) to Name-Count but this is beside the point.

The only difference in the end result is that the order of the list is by name and not by first appearance in the original list:

?- friends_compressed([friends(mike, 4), friends(joe, 3), friends(mike, 1), friends(mike, 2)], R).
R = [friends(joe, 3), friends(mike, 7)].

You can look up the definition of group_pairs_by_key/2 and sum_list/2 in the source code of SWI-Prolog.

Will Ness
  • 70,110
  • 9
  • 98
  • 181
User9213
  • 1,316
  • 6
  • 12
3

One small alteration fixes the problem of duplicate answers:

....
....
compress([], []).
compress([friends(P, C)|R], S) :- 
    % member(friends(P, X), R), !,          NB   either add a cut here
    % \+( \+( member(friends(P, X), R))),   NB   or use double negation
    memberchk(friends(P, X), R),            NB   or use `memberchk/2` if available
    delete_first(R, friends(P, X), E), 
....
....

This also provides the explanation: member succeeds more than once if you have duplicates in the list, but you only intended to use the first result.

Will Ness
  • 70,110
  • 9
  • 98
  • 181
  • I suspect that `member` or `memberchk` followed by `delete_first` is the same as `select` followed by a cut. – User9213 Feb 10 '19 at 13:53
  • there's also [`selectchk/3`](http://www.swi-prolog.org/pldoc/doc_for?object=selectchk/3), I think. bound to do something similar. :) Interestingly, double negation also works (for the given query at least... I mean, it leaves `X` uninstantiated...). – Will Ness Feb 10 '19 at 13:54
  • Yes, there is indeed :) – User9213 Feb 10 '19 at 13:56
  • Double negation is also the somewhat cleaner alternative to failure-driven loops. Funny thing, double negation. – User9213 Feb 10 '19 at 13:58
  • 1
    I guess you meant `\+ (member(X, [1,2,3]), writeln(X), false).` instead of `(member(X, [1,2,3]), writeln(X), false ; true).`. – Will Ness Feb 10 '19 at 14:24
  • 1
    Almost. I meant `\+ ( Generator, \+ Goal )` so for example `\+ ( member(X, [1,2,3]), \+ writeln(X) )` – User9213 Feb 10 '19 at 14:29
3

If you change the definition of delete_first/3 ...

delete_first([X|Y], X, Y).
delete_first([X|Y], E, [X|L]) :- 
   X \= E, 
   delete_first(Y, E, L).

... you don't need to use member/2 anymore ...

compress([], []).
compress([friends(P,C)|R], S) :- 
   delete_first(R, friends(P,X), E), 
   N is C + X, 
   compress([friends(P,N)|E], S).
compress([friends(P,C)|R], [friends(P,C)|S]) :- 
   \+ delete_first(R, friends(P,_), _),
   compress(R, S).

... and the duplicate answers in your sample query disappear:

?- compress([friends(mike,4), friends(joe,3),
             friends(mike,1), friends(mike,2),
             friends(joe,4),  friends(mike,3)], Xs).
Xs = [friends(mike, 10), friends(joe, 7)] ;
false.

However, when used without sufficient instantiation, compress/2 can give spurious answer(s):

?- compress([friends(mike,4), friends(joe,3), friends(Any,10)], Xs).
Any = mike, Xs = [friends(mike,14),friends(joe,3)] ;
false.                             % what?! how about Any = joe?

To safeguard against this, we can use iwhen/2 like so:

list_compressed(Es, Xs) :-
   iwhen(ground(Es), compress(Es,Xs)).

Sample queries:

?- list_compressed([friends(mike,4), friends(joe,3), friends(Any,10)], Xs).
ERROR: Arguments are not sufficiently instantiated

?- list_compressed([friends(mike,4), friends(joe,3),
                    friends(mike,1), friends(mike,2),
                    friends(joe,4),  friends(mike,3)], Xs).
Xs = [friends(mike, 10), friends(joe, 7)] ;
false.
repeat
  • 18,496
  • 4
  • 54
  • 166