How to compare elements in dynamic - prolog

I have two dynamics of /2.
One of the lists, lets call it D2 has set values inside of it. For example: 2 and 3, 4 and 5.
How can I check if my dynamic 1 aka. D1 has all the values inside of it that D2 has and then return true if it does?
I tried to use
member(E, D1(_,_)), member(E, D2(_, _)). So far but without much luck.

This is pretty icky as far as data models go and whatever it is you're trying to do with this is going to at least be inefficient, if it can even be made to work. You'd be far better off defining an arity 3 fact with the first arg being an atom that identifies the type.
That said, you can probably do enough introspection to handle it.
dif(Q, P),
predicate_property(QR, dynamic),
predicate_property(PR, dynamic),
QR =.. [Q, _, _],
PR =.. [P, _, _].
This says, find me two predicates with arity 2, whose heads are different. Ideally, you want just the user-defined predicates. SWI-Prolog cannot do this, but GNU Prolog can, you could add some extra constraints:
predicate_property(QR, user),
predicate_property(PR, user),
This is my solution:
matching(Q, P) :-
dif(Q, P), % different predicates, please
predicate_property(QR, dynamic), % both dynamic
predicate_property(PR, dynamic),
QR =.. [Q, Q1, Q2], % arity-2 predicates, please
PR =.. [P, P1, P2],
findall([Q1, Q2], clause(QR, true), Qs), % find all facts (:- true)
findall([P1, P2], clause(PR, true), Ps),
forall(member(PV, Ps), member(PV, Qs)), % ensure the fact sets are equal
forall(member(QV, Qs), member(QV, Ps)).
Please, please, please DO NOT DO THIS!

Related

How to check order in prolog?

I am trying to solve this puzzle in prolog
Five people were eating apples, A finished before B, but behind C. D finished before E, but behind B. What was the finishing order?
My current solution has singleton variable, I am not sure how to fix this.
finishbefore(A, B, Ls) :- append(_, [A,B|_], Ls).
order(Al):-
length(Al,5),
finishbefore(A,B,Al),
finishbefore(C,A,Al),
finishbefore(D,E,Al),
finishbefore(B,D,Al).
%%query
%%?- order(Al).
Here is a pure version using constraints of library(clpz) or library(clpfd). The idea is to ask for a slightly different problem.
How can an endpoint in time be associated to each person respecting the constraints given?
Since we have five persons, five different points in time are sufficient but not strictly necessary, like 1..5.
:- use_module(library(clpz)). % or clpfd
:- set_prolog_flag(double_quotes, chars). % for "abcde" below.
appleeating_(Ends, Zs) :-
Ends = [A,B,C,D,E],
Zs = Ends,
Ends ins 1..5,
% alldifferent(Ends),
A #< B,
C #< A,
D #< E,
B #< D.
?- appleeating_(Ends, Zs).
Ends = [2, 3, 1, 4, 5], Zs = [2, 3, 1, 4, 5].
There is exactly one solution! Note that alldifferent/1 is not directly needed since nowhere is it stated that two persons are not allowed to end at precisely the same time. In fact, above proves that there is no shorter solution. #CapelliC's solution imposes an order, even if two persons finish ex aequo. But for the sake of compatibility, lets now map the solution back to your representation.
list_nth1(Es, N, E) :-
nth1(N, Es, E).
appleeatingorder(OrderedPeople) :-
appleeating_(Ends, Zs),
same_length(OrderedPeople, Ends),
labeling([], Zs), % not strictly needed
maplist(list_nth1(OrderedPeople), Ends,"abcde"). % effectively enforces alldifferent/1
?- appleeatingorder(OrderedPeople).
OrderedPeople = [c,a,b,d,e].
?- appleeatingorder(OrderedPeople).
OrderedPeople = "cabde".
The last solution using double quotes produces Scryer directly. In SWI use library(double_quotes).
(The extra argument Zs of appleeating_/2 is not strictly needed in this case, but it is a very useful convention for CLP predicates in general. It separates the modelling part (appleeating_/2) from the search part (labeling([], Zs)) such that you can easily try various versions for search/labeling at the same time. In order to become actually solved, all variables in Zs have to have an actual value.)
Let's correct finishbefore/3:
finishbefore(X, Y, L) :-
append(_, [X|R], L),
memberchk(Y, R).
then let's encode the known constraints:
check_finish_time(Order) :-
forall(
member(X<Y, [a<b,c<a, d<e,d<b]),
finishbefore(X,Y,Order)).
and now let's test all possible orderings
?- permutation([a,b,c,d,e],P),check_finish_time(P).
I get 9 solutions, backtracking with ;... maybe there are implicit constraints that should be encoded.
edit
Sorry for the noise, have found the bug. Swap the last constraint order, that is b<d instead of d<b, and now only 1 solution is allowed...

How can I unify this list instead of just adding more variables to it?

I'm doing a project in college and I'm trying to use Prolog, in this case I have to run trough the elements of the list three by three, but I've not been successful at unifying the list with the correct variables (X, Y, Z) and my program keeps adding more and more variables to the list.
aplica_R1_fila_aux(Fila, N_Fila) :-
copia(Fila, N_Fila).
aplica_R1_fila_aux(Fila, [X,Y,Z|T]) :-
aplica_R1_Triplo([X,Y,Z], F),
aplica_R1_fila_aux(Fila, T).
This code it should copy the list Fila to N_Fila then unify [X,Y,Z|T] with N_Fila and change the list but instead it just keeps adding variables to N_Fila.
The main trick you need to make this work is that you can use call/N with varying numbers of arguments. So once you have peeled off X, Y and Z, you can obtain the result of your Goal against them with call(Goal, X, Y, Z, Result).
There are several ways to do this, but I would prefer to just make three sublists and recur on all three of them. When the rightmost one is exhausted, you are done recurring. This gives you fewer base cases to worry about (lists with no, one or two elements do not need to be handled separately) and there are no cuts so your code will wind up looking like this:
map3(Goal, [X,Y,Z|L], Solutions) :-
map3(Goal, [X,Y,Z|L], [Y,Z|L], [Z|L], Solutions).
map3(_, _, _, [], []).
map3(Goal, [X|XR], [Y|YR], [Z|ZR], [R|Rest]) :-
call(Goal, X, Y, Z, R),
map3(Goal, XR, YR, ZR, Rest).
This could also be solved without the helper predicate, but there was something that offended me about it and this really shouldn't be much worse in terms of expense, so this is the way I went.
With a dummy goal of foo(X,Y,Z, foo(X,Y,Z)), I got this example query and result:
?- map3(foo, [a,b,c,d,e,f], Result).
Result = [foo(a, b, c), foo(b, c, d), foo(c, d, e), foo(d, e, f)] ;
false.
I think this is basically what you are trying to get, let me know if I can clarify anything.

Why do we use '!' in prolog

This is the code that i am trying to understand.
co(X) :- co(X,[],L).
co([],A,A):- write(A).
co([X|Xs], A, L) :- p(X-Z,A,R), !, Z1 is Z+1, co(Xs, [X-Z1|R], L).
co([X|Xs], A, L) :- co(Xs, [X-1|A], L).
p(X-Y,[X-Y|R],R):- !.
p(X,[H|Y], [H|Z]) :- p(X,Y,Z).
What is the use of '!' and predicate p(,,) in the above code. OR Can anybody just add comments in every step of the above code so that i can able to understand . Thanks.
There are many things to address in your program. Cuts are not even the major concern. Please, bring me the broom.
Clean up the interface
What is the precise interface you are after? The purpose of co(Xs) currently, is to produce a side effect. Otherwise it can succeed or fail for a given list. But not more than that. Yet, this side effect is not at all needed - and is for most situations not a helpful approach, since such a program is practically unreusable and defies any logical reasoning. You need to leave a hole to let some result lurk out of the relation. Add another argument and remove the goal write/1 in co/3.
co(Xs, D) :-
co(Xs, [], D).
Now you can test the program with the top-level shell alone. You do not need any harness or sandbox to check for the "output". It is there, readily in a separate argument.
Clean up the program structure
Next is co/3 itself. Here, the best is to clarify the intention by separating a bit the concerns, and making these extra arguments a bit more intention-revealing. D stands for dictionary. Another good name would be KVs meaning list (the plural s) of key-value pairs. Note how the different states are numbered: They start with D0, D1, ... and at the end there is D. In this manner, if you start to write a rule, you can put D0,D already in the head without knowing how many states you will need in that rule.
co([], D,D).
co([X|Xs], D0,D) :-
nn(X, D0,D1),
co(Xs, D1,D).
nn(K, D0,D) :-
p(K-V0,D0,D1), !,
V is V0+1,
D = [X-V|D1].
nn(K, D0,D) :-
D = [K-1|D0].
p(X-Y,[X-Y|R],R):- !.
p(X,[H|Y], [H|Z]) :- p(X,Y,Z).
co/3 now more clearly reveals its intention. It somehow relates the elements of a list to some state that is "updated" for each element. There is a word for this: This is a left-fold. And there is even a predicate for it: foldl/4. So we could equally define co/3 as:
co(Xs, D0,D) :-
foldl(nn, Xs, D0,D).
or better get rid of co/3 altogether:
co(Xs, D) :-
foldl(nn, Xs, [], D).
foldl(_C_3, [], S,S).
foldl(C_3, [X|Xs], S0,S) :-
call(C_3, X, S0,S1),
foldl(C_3, Xs, S1,S).
Note, that so far, I have not even touched any cuts of yours, these are now their last moments...
Remover superfluous cuts
The cut in p/3 does not serve any purpose. There is a cut immediately after the goal p/3 anyway. Then, X-Y is not needed in p/3, you can safely replace it by another variable. In short, p/3 is now the predicate select/3 from the Prolog prologue.
select(E, [E|Xs], Xs).
select(E, [X|Xs], [X|Ys]) :-
select(E, Xs, Ys).
nn(K, D0,D) :-
select(K-V0, D0,D1), !,
V is V0+1,
D = [K-V|D1].
nn(K, D0,D) :-
D = [K-1|D0].
This one remaining cut cannot be removed so easily: it protects the alternate clause from being used should K-V not occur in D. However, there are still better ways to express this.
Replace cuts with (\+)/1
nn(K, D0,D) :-
select(K-V0, D0,D1),
V is V0+1,
D = [K-V|D1].
nn(K, D0,D) :-
\+select(K-_, D0,_),
D = [K-1|D0].
Now, each rule states what it wants for itself. This means, that we can now freely change the order of those rules. Call it superstition, but I prefer:
nn(K, D0,D) :-
\+select(K-_, D0,_),
D = [K-1|D0].
nn(K, D0,D) :-
select(K-V0, D0,D1),
V is V0+1,
D = [K-V|D1].
Purify with dif/2
To make this into a true relation, we need to get rid of this negation. Instead of saying, that there is no solution, we can instead demand that all keys (key is the first argument in Key-Value) are different to K.
nokey(_K, []).
nokey(K, [Kx-|KVs]) :-
dif(K, Kx),
nokey(K, KVs).
nn(K, D,[K-1|D]) :-
nokey(K, D).
nn(K, D0,[K-V|D]) :-
select(K-V0, D0,D),
V is V0+1.
With the help of lambdas, nokey(K, D) becomes maplist(K+\(Kx-_)^dif(Kx,K), D)
To summarize, we have now:
co(Xs, D) :-
foldl(nn, Xs, [], D).
nn(K, D,[K-1|D]) :-
maplist(K+\(Kx-_)^dif(Kx,K), D).
nn(K, D0,[K-V|D]) :-
select(K-V0, D0,D),
V is V0+1.
So what is this relation about: The first argument is a list, and the second argument a Key-Value list, with each element and the number of occurrences in the list.
Beginners tend to use !/0 because they are not aware of its negative consequences.
This is because most Prolog textbooks that are popular among beginners are quite bad and often contain wrong and misleading information about !/0.
There is an excellent answer by #false on when to use !/0. In summary: don't.
Instead, focus on a declarative description about what holds, and try to make the description elegant and general using pure and monotonic methods like constraints, clean representations, ...

Prolog planner only generates one plan

I have a prolog planner which works correctly with one major problem of only generating one plan at the time. The plan is correct but for my application I really need to have all the possible plans.
plan(State, Goal, _, Moves) :- subsetB(Goal,State),
write('moves are'), nl,
reverse_print_stack(Moves).
plan(State, Goal, Been_list, Moves) :-
effects(Name, [Preconditions, Add,Delete]), //a list of of rules governing the domain
conditions_met(Preconditions, State), //checks if all preconditions are present in the state
change_state(State, Add,Delete, Child_state), //add predicates from Add list, removes predicates in the Delete list and stores result in Child_state
\+(member_state(Child_state, Been_list)), //checks if Child_state hasn't been previously visited
stack(Child_state, Been_list, New_been_list),
stack(Name, Moves, New_moves),
plan(Child_state, Goal, New_been_list, New_moves).
change_state(S, [],[], S).
change_state(S, [], Delete, S_new) :- change_state(S, [],[], S2),
apply_del(Delete, S2, S_new).
change_state(S, Add,Delete, S_new) :- change_state(S, [], Delete, S2),
apply_add(Add, S2, S_new).
apply_add([],State,State).
apply_add([activate(App)|Rest],State,InterimState) :-apply_add(Rest,State,S2),find_stones(App,State,StonesToBeActivated), make_active(StonesToBeActivated,S2, InterimState).
apply_add([First|Rest],State,InterimState) :- apply_add(Rest,State,S2),add_element(First, S2, InterimState).
apply_del([],InterimState,InterimState).
apply_del([First|Rest],InterimState,NewState) :- apply_del(Rest, InterimState,S2),del_element(First, S2, NewState).
subsetB([],_).
subsetB([F|R],S) :- member(F,S),subsetB(R,S).
%dropping a stone inside app1
effects(drop(X,app1), %action
[[stone(X),active(X)], %preconditions
[in(app1,X)], %postconditions : add list
[active(X)]]). %postconditions : delete list
go(S,G,AllPlans):- findall(Moves, plan(S,G,[S],Moves),AllMoves).
conditions_met(P, S) :- subsetB(P, S).
Sample call
go([in(app1,s1), stone(s2), active(s2),stone(s3),active(s3)],[in(app1,s1),in(app1,s3),in(app1,s2)],AllPlans).
Answer:
drop(s2,app1)
drop(s3,app1) //correct
_2368
_2366
_2364
_2362
_2360
_2358
_2356
_2354
_2352
_2350
_2348
_2346
_2344
_2342
_2340
_2338
_2336
etc... infinitely
For finding all solutions to a goal, look at bagof or findall. Or am I missing something?
Like this:
?- findall(Moves, plan(State, Goal, _, Moves), AllMoves).
The whole idea of these predicates is that you say which arguments you want to collect and get a list of all possible instantiations under that predicate. In this sense you normally have a "return" value (an argument that gets instantiated with the result) that you can then look at or print, instead of printing it explicitly in the predicate that finds solutions.
A simplistic example:
foo(1). foo(2). foo(3). foo(4). foo(5). foo(6).
bar(R) :- foo(A), A mod 2 =:= 0.
findall(R, bar(R), Even).
Now to recursion: how does it work? You cannot share variables between different clauses of the same predicate. For example, this is wrong:
baz(0, B).
baz(X, B) :- X0 is X - 1, B1 is B + 1, baz(X0, B1).
because B is a singleton variable in the first clause of baz. Instead, you can do:
baz(0, B, B).
baz(X, B, Result) :- X0 is X - 1, B1 is B + 1, baz(X0, B1, Result).
which you can now call:
?- baz(10, 2, Result).
Result = 12
but you will still run into problems after the first answer.
You get the single correct plan probably because the first clause of plan does not meet the requirements of subsetB, and you get to the second clause. There, you make a Moves that has a free variable at its Tail, but this is not a problem yet. The problem is, however, that when you find your first solution (all in the second plan clause, recursively), Moves is now bound to a list of actions, and instead of starting to look for a new solution, you get into the second clause again by backtracking, with the already filled in Moves, which probably messes up the rest of the algorithm.
To make it correct, you probably need to make sure that when your plan backtracks, it starts to look for a new solution, with a clean Moves. You can start by instantiating Moves to an empty list and collecting results in an accumulator, as shown in the simplistic baz predicate above.

Prolog difference routine

I need some help with a routine that I am trying to create. I need to make a routine that will look something like this:
difference([(a,b),(a,c),(b,c),(d,e)],[(a,_)],X).
X = [(b,c),(d,e)].
I really need help on this one..
I have written a method so far that can remove the first occurrence that it finds.. however I need it to remove all occurrences. Here is what I have so far...
memberOf(A, [A|_]).
memberOf(A, [_|B]) :-
memberOf(A, B).
mapdiff([], _, []) :- !.
mapdiff([A|C], B, D) :-
memberOf(A, B), !,
mapdiff(C, B, D).
mapdiff([A|B], C, [A|D]) :-
mapdiff(B, C, D).
I have taken this code from listing(subtract).
I don't fully understand what it does, however I know it's almost what I want. I didn't use subtract because my final code has to be compatible with WIN-Prolog... I am testing it on SWI Prolog.
Tricky one! humble coffee has the right idea. Here's a fancy solution using double negation:
difference([], _, []).
difference([E|Es], DL, Res) :-
\+ \+ member(E, DL), !,
difference(Es, DL, Res).
difference([E|Es], DL, [E|Res]) :-
difference(Es, DL, Res).
Works on SWI-PROLOG. Explanation:
Clause 1: Base case. Nothing to diff against!
Clause 2: If E is in the difference list DL, the member/2 subgoal evaluates to true, but we don't want to accept the bindings that member/2 makes between variables present in terms in either list, as we'd like, for example, the variable in the term (a,_) to be reusable across other terms, and not bound to the first solution. So, the 1st \+ removes the variable bindings created by a successful evaluation of member/2, and the second \+ reverses the evaluation state to true, as required. The cut occurs after the check, excluding the 3rd clause, and throwing away the unifiable element.
Clause 3: Keep any element not unifiable across both lists.
I am not sure, but something like this could work. You can use findall to find all elements which can't be unified with the pattern:
?- findall(X, (member(X, [(a,b),(b,c),(a,c)]), X \= (a,_)), Res).
gets the reply
Res = [ (b, c) ]
So
removeAll(Pattern, List, Result) :-
findall(ZZ109, (member(ZZ109, List), ZZ109 \= Pattern), Result).
should work, assuming ZZ109 isn't a variable in Pattern (I don't know a way to get a fresh variable for this, unfortunately. There may be a non-portable one in WIN-Prolog). And then difference can be defined recursively:
difference(List, [], List).
difference(List, [Pattern|Patterns], Result) :-
removeAll(Pattern, List, Result1),
difference(Result1, Patterns, Result).
Your code can be easily modified to work by making it so that the memberOF predicate just checks to see that there is an element in the list that can be unified without actually unifying it. In SWI Prolog this can be done this way:
memberOf(A, [B|_]) :- unifiable(A,B,_).
But I'm not familiar with WIN-PRolog so don't know whether it has a predicate or operator which only tests whether arguments can be unified.

Resources