9

I'm trying to solve a new program with Prolog, and I'm stuck, and don't know how to continue... I must do a predicate that has 3 arguments, the first is a list of elements, the second one is a list of tuples, and the third one must be a list returned that contains the second element of the tuples, if the first element of the tuple match with an element of the first argument list. It must delete copies also!!

For example,

check([a,c],[(a,aa),(bb,bbb),(a,aa),(c,def)],X).
X = [aa, def] .

As you can see, a and c match on the list of tuples, so return the second element of the tuples.

So it works, BUT if there is more than one tuple that contains a first element that match on the first list, it only will take once, for example:

check([a,b],[(a,c),(a,d),(b,c),(b,e),(c,f)],X).
X = [c] .

It finds a the first time and took c, and b the first time and took c again, but not iterate to find more a or b, the right result should be X=[c,d,e].

So please, I ask you help on how to solve this situation or any clue to solve it...

Here is my code:

check([],_,[]).
check(L,DIC,Xord) :- inter(L,DIC,X), list_to_set(X,Xord).

inter([],_,[]).
inter(L1, DIC, L3) :- 
   L1 = [H|T], 
   DIC = [(DIC1,DIC2)|_], 
   H == DIC1, 
   L3 = [DIC2|L3T], 
   inter(T, DIC, L3T).
inter(L1,[_|DIC],L3) :- inter(L1,DIC,L3).
inter([_|T], DIC, L3) :- inter(T, DIC, L3).

Thanks in advance for your time.

false
  • 10,264
  • 13
  • 101
  • 209
rubitops
  • 115
  • 1
  • 8

6 Answers6

8

For an easier understandable version I propose the following:

:- use_module(library(lists)).

keys_dict_uniquevalues(Ks,D,UVs) :-
    keys_dict_values(Ks,D,Vs),              % Vs ... values with duplicates
    list_set(Vs,UVs).                       % UVs ... Vs deduplicated

keys_dict_values([],_D,[]).                 % No keys no values
keys_dict_values([Key|Keys],D,Vs) :-    
    key_dict_values(Key,D,Matches),         % all Matches for Key
    keys_dict_values(Keys,D,OtherVs),       % Matches for other Keys
    append(Matches,OtherVs,Vs).             % all found values in Vs

key_dict_values(_K,[],[]).                  % no mathes if dictionary empty
key_dict_values(K,[(K,V)|Pairs],[V|Vs]) :-  % Value is in list if key matches 
    key_dict_values(K,Pairs,Vs).
key_dict_values(K,[(X,_V)|Pairs],Vs) :-     % Value is not in list
    dif(K,X),                               % if key doesn't match
    key_dict_values(K,Pairs,Vs).

list_set([],[]).                            % empty list contains no duplicates
list_set([X|Xs],[X|Ys]) :-                  % head of the first list
    subtract(Xs,[X],Zs),                    % doesn't occur in Zs
    list_set(Zs,Ys).

If you want so write a program without the use of library(lists) you have to replace the goal append/3 in keys_dict_values/3 and the goal subtract/3 in list_set/2. In the below example by lists_appended/3 and list_x_removed/3:

keys_dict_uniquevalues(Ks,D,UVs) :-
    keys_dict_values(Ks,D,Vs),
    list_set(Vs,UVs).

keys_dict_values([],_D,[]).
keys_dict_values([Key|Keys],D,Vs) :-
    key_dict_values(Key,D,Matches),
    keys_dict_values(Keys,D,OtherVs),
    lists_appended(Matches,OtherVs,Vs).

key_dict_values(_K,[],[]).
key_dict_values(K,[(K,V)|Pairs],[V|Vs]) :-
    key_dict_values(K,Pairs,Vs).
key_dict_values(K,[(X,_V)|Pairs],Vs) :-
    dif(K,X),
    key_dict_values(K,Pairs,Vs).

lists_appended([],L,L).
lists_appended([X|Xs],Ys,[X|Zs]) :-
    lists_appended(Xs,Ys,Zs).

list_set([],[]).
list_set([X|Xs],[X|Ys]) :-
    list_x_removed(Xs,X,Zs),
    list_set(Zs,Ys).

list_x_removed([],_X,[]).
list_x_removed([X|Xs],X,Ys) :-
    list_x_removed(Xs,X,Ys).
list_x_removed([X|Xs],Z,[X|Ys]) :-
    dif(X,Z),
    list_x_removed(Xs,Z,Ys).

The queries given in the above exmaple work for both versions:

?- keys_dict_uniquevalues([a,c],[(a,aa),(bb,bbb),(a,aa),(c,def)],X).
X = [aa,def] ? ;
no
?- keys_dict_uniquevalues([a,b],[(a,c),(a,d),(b,c),(b,e),(c,f)],L).
L = [c,d,e] ? ;
no

The counterexample provided by @false fails for both versions as expected:

?- keys_dict_uniquevalues([a,b],[(a,c),(a,d),(b,c),(b,e),(c,f)],[c,c]).
no

The unusual usage as suggested by @false:

   ?- keys_dict_uniquevalues([a,b],[KV1,KV2],[e]).
KV1 = KV2 = (a,e) ? ;
KV1 = (a,e),
KV2 = (b,e) ? ;
KV1 = (a,e),
KV2 = (_A,_B),
dif(b,_A),
dif(a,_A) ? ;
KV1 = (b,e),
KV2 = (a,e) ? ;
KV1 = (_A,_B),
KV2 = (a,e),
dif(b,_A),
dif(a,_A) ? ;
KV1 = KV2 = (b,e) ? ;
KV1 = (b,e),
KV2 = (_A,_B),
dif(b,_A),
dif(a,_A) ? ;
KV1 = (_A,_B),
KV2 = (b,e),
dif(b,_A),
dif(a,_A) ? ;
no
tas
  • 8,100
  • 3
  • 14
  • 22
  • `KV1 = KV2 = (a,e)` a solution? Hm, I would not interpret the question to this end. But it is an interpretation, nevertheless. – false Apr 07 '16 at 19:22
  • @false: True, it is a debatable interpretation. – tas Apr 07 '16 at 20:03
5

So far, your problem statement and your subsequent explanations are a bit contradictory. Let's see if this fits.

Relational names.

As the very first, try to describe your problem as a relation and not as a sequence of actions or commands. To better outline this, try to find a name for the relation that does not suggest that something has to be done. Instead, describe each argument one by one. You frowned upon this in a comment, observing that "it's just a name". Of course, just a name. But that's all what a programmer has. Names all over. If every name is just arbitrarily chosen, or even misguiding you will have a very rough time programming.

So what do you have:

  1. A list with elements used as keys. Note that keys is a plural. And in Prolog many plurals stand for lists.

  2. Some dictionary, or dict with (K, V) elements. Actually, in Prolog, we use more commonly (K-V) instead and call this a pair, consequently pairs would be quite fitting, too. But lets stay with your definition.

  3. A list of values. The list does not possess duplicates. We could call this a list of unique values, or uvalues.

Now all of it together makes a nice relation:

 keys_dict_uvalues(Keys, Dict, UValues)

Imagine how to use it

Before rushing to actual coding, just visualize that you have already written it, and now you want to use it. Or: maybe you will find someone who will write the predicate for you. But how can you be sure that the code is working? So collect some test cases together. Best start with ground queries:

?- keys_dict_uniquevalues([a,c],[(a,aa),(bb,bbb),(a,aa),(c,def)],[aa,def]).

Given that, we could leave out certain parts by introducing variables:

?- keys_dict_uniquevalues([K1,K2],[(a,aa),(bb,bbb),(a,aa),(c,def)],[aa,def]).

How many solutions do you expect here? I think it's only one. Sure? At that point in time such considerations are very valuable.

But now for the coding. I often like a top down approach:

keys_dict_uniquevalues(Ks, KVs, Vsu) :-
   keys_dict_values(Ks, KVs, Vs),
   list_nub(Vs, Vsu).

keys_dict_values(Ks, KVs, Vs) :-
   maplist(list_pmemberv(KVs), Ks, Vs).

list_pmemberv(KVs, K, V) :-      % the first fitting K
   tmember(k_v_p_t(K,V), KVs).

k_v_p_t(K, V, (Ki, Vi), T) :-
   if_(K = Ki, ( Vi = V, T = true ), T = false).

list_nub([], []).
list_nub([E|Es], [E|Gs]) :-
   tfilter(dif(E), Es, Fs),
   list_nub(Fs, Gs).

Above uses some definitions defined in other examples: maplist/3, if_/3, tmember/2, tfilter/3, (=)/3, dif/3.

Here are some examples, that are rather unusual:

How must a dictionary with two entries look like such that a and b are both mapped to e?

?- keys_dict_uniquevalues([a,b],[KV1,KV2],[e]).
   KV1 = (a,e), KV2 = (b,e)
;  KV1 = (b,e), KV2 = (a,e)
;  false.

So there are two possibilities.

false
  • 10,264
  • 13
  • 101
  • 209
  • 2
    Well, really thanks you for your answer. Now I will remember your advices everytime I must pick a name :). In the other hand, I will take a look deeper on your functions used in other examples. Anyway, I understood the overall process. Yes Im agree that there are two possibilities, but it is the same pairs, just with different order. Again thanks you for your constructive answer. – rubitops Mar 31 '16 at 19:04
  • 1
    @false: Regarding the query `?- keys_dict_uniquevalues([a,b],[KV1,KV2],[e]).`: I think there are six additional solutions. I edited my non-dcg version to include that query. – tas Apr 07 '16 at 19:17
5

On a second thought, this relation is really all about lists and therefore an excellent candidate for DCGs:

keys_dict_uniquevalues(K,D,UVs) :-
    phrase(keys_values(K,D),Vs),
    phrase(uniques(Vs),UVs).

keys_values([],_D) -->                 % no keys no values
    [].
keys_values([K|Keys],D) -->
    key_values(K,D),                   % the values for key K
    keys_values(Keys,D).               % followed by values for other keys

key_values(_K,[]) -->                  % no values left for key _K
    [].
key_values(K,[(K2,V)|Pairs]) -->       % values for
    {dif(K,K2)},                       % different keys are not in the list
    key_values(K,Pairs).
key_values(K,[(K,V)|Pairs]) -->        % values for en equal key
    [V],                               % are in the list
    key_values(K,Pairs).

uniques([]) -->                        % the empty list has no duplicates
    [].
uniques([X|Xs]) -->
    [X],                               % X is in the list
    {phrase(list_without(Xs,X),XRs)},  % once
    uniques(XRs).

list_without([],_X) -->                % no X in the empty list
    [].
list_without([X|Xs],X) -->             % X is not in the list
    list_without(Xs,X).
list_without([Y|Ys],X) -->
    [Y],                               % Y is in the list
    {dif(X,Y)},                        % if it is different from X
    list_without(Ys,X).

I find this version even easier to read than my non-DCG version (see the comments in the code). The interface is the same in both versions so my above queries work one-to-one for this version. The query

   ?- keys_dict_uniquevalues([a,b],[KV1,KV2],[e]).

also yields the same results just in opposite order.

repeat
  • 18,496
  • 4
  • 54
  • 166
tas
  • 8,100
  • 3
  • 14
  • 22
  • 2
    Very nice! Only a very minor comment regarding`removed//2`: better name and argument order: `list_without//2`. For several reasons, notably also to follow the pattern of the other rules, I suggest to write the body of the last clause as: `[Y], { dif(X,Y) }, ...`, i.e., reorder the first two goals. – mat Apr 07 '16 at 19:20
  • 3
    @mat: You are right. It looks better this way. Putting the dif/2 goal first was out of habit. I like to put cheap goals first but in this case it doesn't make much of a difference. – tas Apr 07 '16 at 19:59
2

First, what

check([],_,_).

is supposed to do ? I would drop it.

Then, why do you sort everything ? I would avoid doing useless work...

Last, you need 2 unrelated scan of lists: the first one to get access to keys, the second one to search the value associated to key.

So, your code is not easy to correct without rewriting from scratch. And then consider builtins:

check(Keys,Dict,Values) :-
  findall(V, (member(K, Keys), memberchk((K,V),Dict)), Values).
CapelliC
  • 59,646
  • 5
  • 47
  • 90
  • Well I made some mistakes, as you said, the first check([],_,_)., was suppose to be for a empty list, now its fixed. I used sort, to delete copies, but I will use now list_to_set. I will work now in your final advices, about the 2 scans. – rubitops Mar 30 '16 at 15:15
  • 1
    Really thanks you, after taking a look deeper, and understanding it, now its working. I only had to change the second memberchk to member, because i wanted all results not only the first, and then deleting duplicates. Thanks again – rubitops Mar 30 '16 at 16:01
  • @CapelliC generally, where is the deference between predicat and predicate**chk** – Ans Piter Mar 30 '16 at 16:27
  • @AnsPiter: memberchk/2 is like member/2 followed by a cut. But in SWI-Prolog is implemented at low level, in C and with attention to efficiency. – CapelliC Mar 30 '16 at 16:29
  • @CapelliC why it followed by a cut ? is it mean it stoped when it find the first occurrence of Elem in list ? – Ans Piter Mar 30 '16 at 16:42
  • @AnsPiter: exactly – CapelliC Mar 30 '16 at 16:48
  • @rubitops: Why have you accepted this solution, it succeeds for: `check_cc([a,b],[(a,c),(a,d),(b,c),(b,e),(c,f)],[c,c]).` – false Mar 30 '16 at 21:32
  • @false It helped me to solve my problem, as I said, I got to modify his code, but after these 2 editions I did, I try your example and say its false. – rubitops Mar 31 '16 at 19:13
  • @CapelliC: Note that SWI's `memberchk/2` is about half the speed of SICStus' definition which is simply `once(member(E,Es))`... – false Mar 31 '16 at 19:47
1
:- import append/3, member/2 from basics.

remove_duplicates([], []).

remove_duplicates([X | Y], Z) :- member(X, Y), !, remove_duplicates(Y, Z).

remove_duplicates([X | Y], [X | Z]) :- remove_duplicates(Y, Z).

hcheck(_, [], []).

hcheck(X, [(X, Y) | L], R) :- !, hcheck(X, L, RR), append([Y], RR, R).

hcheck(X, [_ | L], R) :- hcheck(X, L, R).

check([], _, []).

check([X | Y], L, R) :- hcheck(X, L, RR), check(Y, L, RRR), append(RR, RRR, RRRR), remove_duplicates(RRRR, R).

/********/

/* test */

/********/

[check loaded]

yes
| ?- check([a,c],[(a,aa),(bb,bbb),(a,aa),(c,def)],X).

X = [aa,def];

no
| ?- check([a,b],[(a,c),(a,d),(b,c),(b,e),(c,f)],X).

X = [d,c,e];

no

check/hcheck just form a double loop. check selects elements from the first list while hcheck matches the element to tuples in the second list. Results are simply appended; at the end, duplicates are removed. I am not an expert (just learned Prolog), so I do not know how good this solution is but it seems to work OK.

Marek
  • 11
  • 3
  • 1
    Code-Only answeres are not from high value. If you could add some explanations this would be much more helpful for the future. – ckruczek Feb 24 '17 at 12:55
  • Sorry; check/hcheck just form a double loop. check selects elements from the first list while hcheck matches the element to tuples in the second list. Results are simply appended; at the end, duplicates are removed. I am not an expert (just learned Prolog), so I do not know how good this solution is but it seems to work OK. – Marek Feb 24 '17 at 13:07
0

EDIT :

check([],_,[]).

check([X|Xs],List,[R|Rs]):-
        check_(X,List,R),
        check(Xs,List,Rs).

check_(_,[],[]).
check_(X,[(Z,Y)|Xs],Res):-
        X=Z->
        Res=[Y|Ys],
        check_(X,Xs,Ys);
        Res=Ys,
        check_(X,Xs,Ys).

Test :

    | ?- check([a,c],[(a,aa),(bb,bbb),(a,aa),(c,def)],X).
X = [[aa,aa],[def]] ? ;
no

    check([a,b],[(a,c),(a,d),(b,c),(b,e),(c,f)],X).
X = [[c,d],[c,e]] ? ;
no
Ans Piter
  • 573
  • 1
  • 5
  • 17
  • @false I use CUT'!' in order to ; if I find the element X, I stopped the predicate which returned the first appearance of Y – Ans Piter Mar 30 '16 at 14:04
  • 1
    If you want to learn s-t: first choose a relational name. Then these other issues can be looked at. – false Mar 30 '16 at 14:27
  • Thanks you, but this is not working. for example try this: check([a,b],[(a,c),(a,d),(b,c),(b,e),(c,f)],X). I hope that with your construction can improve mine, I will take a look deeper ;). – rubitops Mar 30 '16 at 15:34
  • @rubitops can you tape the expected result for this query – Ans Piter Mar 30 '16 at 16:22
  • Yes, the result is X = [c, d, e]. – rubitops Mar 30 '16 at 16:59