Assigning different numbers to variables in a term - prolog

I'm trying to create a predicate, which will generate all possible evalutions of a compound term with numbers, e.g. assign_distinct_values([A-B], E). should yield 99 results.
However, I can't find the nondeterminism in my current effort:
assign_distinct_values(E, A) :-
term_variables(E, V),
assign_distinct_values(E, V, [0,1,2,3,4,5,6,7,8,9], A).
assign_distinct_values(E, [], [], E).
assign_distinct_values(E, [], _, E).
assign_distinct_values(E, V, N, A) :-
select(Num, N, N2),
select(Var, V, V2),
Var is Num,
assign_distinct_values(E, V2, N2, A).
which generates a symmetrical result with duplicates like:
1-0
0-1
0-1
1-0

First consider using a more meaningful naming convention: I recommend appending an "s" to the names of variables that denote lists, and numbering them more systematically (starting from 0), and using a more declarative and meaningful predicate name:
with_distinct_integers(E0, E) :-
term_variables(E0, Vs),
with_distinct_integers(E0, Vs, [0,1,2,3,4,5,6,7,8,9], E).
with_distinct_integers(E, [], [], E).
with_distinct_integers(E, [], _, E).
with_distinct_integers(E0, Vs0, Ns0, E) :-
select(Num, Ns0, Ns),
select(Var, Vs0, Vs),
Var is Num,
with_distinct_integers(E0, Vs, Ns, E).
Focusing on with_distinct_integers/4 now. You see that the first clause is subsumed by the second, so you can omit the first clause without losing solutions. The variable Var is only used to unify it with Num, so you can use a single variable right away:
with_distinct_integers(E, [], _, E).
with_distinct_integers(E0, Vs0, Ns0, E) :-
select(Num, Ns0, Ns),
select(Num, Vs0, Vs),
with_distinct_integers(E0, Vs, Ns, E).
You still find unintended duplicate solutions with this simplified version, and I leave it as an easy exercise to find out what causes this:
?- with_distinct_integers(X-Y, [X,Y], [0,1], A).
..., A = 0-1 ;
..., A = 1-0 ;
..., A = 1-0 ;
..., A = 0-1 ;
false.
Hint: Just reason declaratively over the simplified definition. Continuing with the simplification: Why pass around the original term when you already have everything you need, i.e., its variables, available? Consider:
with_distinct_integers(E) :-
term_variables(E, Vs),
numlist(0, 9, Ns),
with_distinct_integers(Vs, Ns).
with_distinct_integers([], _).
with_distinct_integers([V|Vs], Ns0) :-
select(V, Ns0, Ns),
with_distinct_integers(Vs, Ns).
Example query, counting all solutions:
?- findall(., with_distinct_integers([X-Y]), Ls), length(Ls, L).
Ls = ['.', '.', '.', '.', '.', '.', '.', '.', '.'|...],
L = 90.
Surprise on the side: there are only 90 solutions, not 99.
Also consider using finite domain constraints, which are relations over integers that let you easily formulate such tasks:
:- use_module(library(clpfd)).
with_distinct_integers(E) :-
term_variables(E, Vs),
Vs ins 0..9,
all_different(Vs),
label(Vs).
Example query:
?- with_distinct_integers(X-Y).
X = 0,
Y = 1 ;
X = 0,
Y = 2 ;
X = 0,
Y = 3 .

L being the list of values and E, A the output variables
assign_distinct_values(E, A, L) :-
member(E,L),
delete(L,E,L1),
member(A,L1).
using prolog predicates is quite quicker. member(X,L) checks if X is in L, if so, we create a new list L1 not containing X with delete(L,X,L1) and check again for a second member the same way.
Another version :
assign_distinct_values(E, A) :-
L = [0,1,2,3,4,5,6,7,8,9],
member(E,L),
delete(L,E,L1),
member(A,L1).
Does it work ? I don't have prolog installed on my machine.
Regards

Related

How do I see a detailed order (execution) for a Prolog query?

Let's say I have this Prolog program:
loves(vincent, mia).
loves(marcellus, mia).
jealous(A, B) :- loves(A, C), loves(B, C).
With query jealous(A,B). I'm very new to Prolog and I'd like to know how is it possible to see the exact order the program will be running and taking its ways for this query? I have tried using trace, jealous(A,B). command but it has only given me that:
Isn't there any more detailed solution for that? :/
Have you seen the Prolog Visualizer?
When you get to the page be sure to click on the icons in the upper right to learn more.
Enjoy.
Screenshot after step 10 of 49.
Screenshot for example given after all steps.
The Prolog Visualizer uses a slightly nonstandard way to enter a query by ending the query with a question mark (?), e.g.
jealous(A,B)?
If you do not post a query in the input area on the left you will receive an error, e.g.
The input for the Prolog Visualizer for your example is
loves(vincent, mia).
loves(marcellus, mia).
jealous(A, B) :- loves(A, C), loves(B, C).
jealous(A,B)?
When the Prolog Visualizer completes your example, notice the four results in green on the right
If you are using SWI-Prolog and after you understand syntactic unification, backtracking and write more advanced code you will find this of use:
Overview of the SWI Prolog Graphical Debugger
For other useful Prolog references see: Useful Prolog references
If the Prolog system has callable_property/2 and sys_rule/3, then one can code
a smart "unify" port as follows, showing most general unifiers (mgu's`):
:- op(1200, fx, ?-).
% solve(+Goal, +Assoc, +Integer, -Assoc)
solve(true, L, _, L) :- !.
solve((A, B), L, P, R) :- !, solve(A, L, P, H), solve(B, H, P, R).
solve(H, L, P, R) :- functor(H, F, A), sys_rule(F/A, J, B),
callable_property(J, sys_variable_names(N)),
number_codes(P, U), atom_codes(V, [0'_|U]), shift(N, V, W),
append(L, W, M), H = J, reverse(M, Z), triage(M, Z, I, K),
offset(P), write_term(I, [variable_names(Z)]), nl,
O is P+1, solve(B, K, O, R).
% triage(+Assoc, +Assoc, -Assoc, -Assoc)
triage([V=T|L], M, R, [V=T|S]) :- var(T), once((member(W=U, M), U==T)), W==V, !,
triage(L, M, R, S).
triage([V=T|L], M, [V=T|R], S) :-
triage(L, M, R, S).
triage([], _, [], []).
% shift(+Assoc, +Atom, -Assoc)
shift([V=T|L], N, [W=T|R]) :-
atom_concat(V, N, W),
shift(L, N, R).
shift([], _, []).
% offset(+Integer)
offset(1) :- !.
offset(N) :- write('\t'), M is N-1, offset(M).
% ?- Goal
(?- G) :-
callable_property(G, sys_variable_names(N)),
shift(N, '_0', M),
solve(G, M, 1, _).
Its not necessary to modify mgu's retrospectively, since a solution to a
Prolog query is the sequential composition of mgu's. Here is an example run:
?- ?- jealous(A,B).
[A_0 = X_1, B_0 = Y_1]
[H_1 = mia, X_1 = vincent]
[Y_1 = vincent]
A = vincent,
B = vincent ;
[Y_1 = marcellus]
A = vincent,
B = marcellus ;
Etc..
This is a preview of Jekejeke Prolog 1.5.0 the new
predicate sys_rule/3, its inspired by the new
predicate rule/2 of SWI-Prolog, but keeps the
clause/2 argument of head and body and uses a predicate
indicator.

Prolog lists transforming

I want to transform a list in this format:
C=[via(A,B,C,D),via(G,T,H,U),via(J,O,L,P)]
into the following:
F=[(C,D),(H,U),(L,P)]
The letters from F correspond to the letters from C.
It could be something like:
transform([], []).
transform([via(_, _, X, Y)|T)], [(X, Y)|TT) :-
transform(T, TT).
Using library(lambda) it comes down to:
..., maplist(\via(_,_,X,Y)^(X,Y)^true, C, F), ...
several Prologs (like SWI-Prolog I'm using here, in library(apply)) have maplist:
1 ?- [user].
|: transform(via(_,_,C,D),(C,D)).
(ctrl+D here)
true.
2 ?- X = [via(A,B,C,D),via(G,T,H,U),via(J,O,L,P)], maplist(transform,X,Y).
X = [via(A, B, C, D), via(G, T, H, U), via(J, O, L, P)],
Y = [ (C, D), (H, U), (L, P)].

Intersection of two lists of variables

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.

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).

swi Prolog - Error arguments not sufficiently Instantiated

I am new to Prolog and when I query
sortedUnion([1,1,1,2,3,4,4,5], [0,1,3,3,6,7], [0,1,2,3,4,5,6,7]).
I get an error
Exception: (7) unite([_G114, _G162, _G201, _G231, _G243], [_G249, _G297, _G336, _G357, _G369], [0, 1, 2, 3, 4, 5, 6, 7]) ?
So I am hoping someone will be able to tell me where my code is mistaken and why it is wrong?
%undup(L, U) holds precisely when U can be obtained from L by eliminating repeating occurrences of the same element
undup([], []).
undup([X|Xs], [_|B]) :- remove(X,Xs,K), undup(K, B).
remove(_,[],[]).
remove(Y,[Y|T],D) :- remove(Y,T,D).
remove(Y,[S|T],[S|R]) :- not(Y = S), remove(Y,T,R).
%sortedUnion(L1,L2,U) holds when U contains exactly one instance of each element
%of L1 and L2
sortedunion([H|T], [S|R], [F|B]) :- undup([H|T], N), undup([S|R], M), unite(N,M,[F|B]).
unite([], [], []).
unite([X], [], [X]).
unite([], [X], [X]).
unite([H|T], [S|R], [X|Xs]) :- S=H, X is S, unite(T, R, Xs).
unite([H|T], [S|R], [X|Xs]) :- H<S, X is H, unite(T, [S|R], Xs).
unite([H|T], [S|R], [X|Xs]) :- S<H, X is S, unite([H|T], R, Xs).
An advice first: try to keep your code as simple as possible. Your code can reduce to this (that surely works)
sortedunion(A, B, S) :-
append(A, B, C),
sort(C, S).
but of course it's instructive to attempt to solve by yourself. Anyway, try to avoid useless complications.
sortedunion(A, B, S) :-
undup(A, N),
undup(B, M),
unite(N, M, S).
it's equivalent to your code, just simpler, because A = [H|T] and so on.
Then test undup/2:
1 ?- undup([1,1,1,2,3,4,4,5],L).
L = [_G2760, _G2808, _G2847, _G2877, _G2889] ;
false.
Clearly, not what you expect. The culprit should that anon var. Indeed, this works:
undup([], []).
undup([X|Xs], [X|B]) :- remove(X,Xs,K), undup(K, B).
2 ?- undup([1,1,1,2,3,4,4,5],L).
L = [1, 2, 3, 4, 5] ;
false.
Now, unite/3. First of all, is/2 is abused. It introduces arithmetic, then plain unification suffices here: X = S.
Then the base cases are hardcoded to work where lists' length differs at most by 1. Again, simpler code should work better:
unite([], [], []).
unite( X, [], X).
unite([], X, X).
...
Also, note the first clause is useless, being already covered by (both) second and third clauses.

Resources