Prolog planner only generates one plan - prolog

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.

Related

delete all occurences of a term in a list

I know this sounds "duplicate" but please help me out
I have defined three terms as follows:
type([a, b, c, d]:location).
type([coffee, tea, lemonade, water, biscuits]: object).
type([order(object, location)]: order).
I have a piece of code that then generates a list of random orders.
I now need a predicate that deletes all the terms that unify with order(X, a), that is, deletes all the orders that have a as location from that list.
For instance, this is an example of list (printed this way to make it readable):
order(tea,a)
order(tea,b)
order(coffee,b)
order(water,c)
order(lemonade,d)
order(biscuits,a)
order(water,c)
order(tea,c)
order(coffee,d)
order(water,d)
applying such needed predicate my_delete(List, [order(_, a), order(_, b)], Result) would give:
order(water,c)
order(lemonade,d)
order(water,c)
order(tea,c)
order(coffee,d)
order(water,d)
So far I've tried to remove a sublist from the main list, but what it does is just delete a single element for a and a single element for b, not all of them. This is the code for such predicate (thanks also to this reference):
remove_list([], _, []).
remove_list([X|Tail], L2, Result):-
member(X, L2),
!,
remove_list(Tail, L2, Result).
remove_list([X|Tail], L2, [X|Result]):-
remove_list(Tail, L2, Result).
and a query that I tried, but didn't work as expected, was:
remove_list(Input_list, [ordine(_, a), ordine(_, b)], Result).
Notice that I need duplicates, so using sets won't work.
You can use negation \+ to avoid further unification over recursion of your filter list:
remove_list([], _, []).
remove_list([X|Tail], ToDelete, Result):-
(\+( memberchk(X, ToDelete) ) ->
Result=[X|NResult] ;
Result=NResult
),
remove_list(Tail, ToDelete, NResult).
Using exclude/3, which takes a predicate, input list and output list:
rev_memberchk(List, Member) :-
memberchk(Member, List).
my_delete(Input_List, Orders, Result) :-
exclude(rev_memberchk(Orders), Input_List, Result).
Using memberchk/1 rather than member/2 for efficiency; you don't need the bound output, just to know if it can unify. If you also have lambda expressions, this can be turned into a one-liner by removing the need to write a predicate with re-ordered arguments:
my_delete(Input_List, Orders, Result) :-
exclude({Orders}/[X]>>memberchk(X, Orders), Input_List, Result).

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.

Writing an unnamed variable

I am writing a program in Prolog (gprolog) that pathfinds on a graph. I based it partially off of this SO post.
Let me give an example. Here is an example graph I drew:
And here is what the code initially looked like:
path([Goal],Goal,Goal).
path(P,Start,Goal) :- adjacent(Start,X),
\+ (memberchk(X,P)),
(
Goal=X
;
path([Start|P],X,Goal)
).
Regardless of whether that base case is redundant, here is the problem. I want an input style of
| ?- path(P,a,f).
and for that input, I would get output of
P = [a,s,f]
true ?
However, the problem with the code as it stands lies with memberchk. For memberchk(a,P), it attempt to unify, calls memberchk(a,[a|_]), and returns true. I don't want this to happen, so I first check if P is instantiated using the var/1 predicate. Thus, my code changed to
path([Goal],Goal,Goal).
path(P,Start,Goal) :- var(P),
path([],Start,Goal).
path(P,Start,Goal) :- adjacent(Start,X),
\+ (memberchk(X,P)),
(
Goal=X
;
path([Start|P],X,Goal)
).
Now if P is uninstantiated, we call path/3 with the empty list. My problem is this: now I cannot print P at the end, as I call path([],Start,Goal) and P is no longer associated with [].
I have tried using the write/1 predicate, but it either printed out P at every step or printed P = _26 (meaning it's printing the uninstantiated P, not the final value of P).
I hope this is a simple problem, I'm just awfully new to Prolog.
Apologies if something similar has been asked; I would love to be pointed to other questions that could help. I searched through SO and Google before posting this.
The concept you need is that of accumulators
You were actually very close: you realized indeed that initializing P to [], and filling it with [Start|P] as you recurse was a working strategy. This is called an accumulator, and to get the final result you simply need to add another argument.
Here is your new path/3 predicate that you query:
path(P, Start, Goal) :-
path([], P, Start, Goal).
As you can see, here we add the [] as a first argument to path/4, which we implement like this:
path(L, P, Goal, Goal) :-
reverse([Goal|L], P).
path(L, P, Start, Goal) :-
adjacent(Start, X),
\+ (memberchk(X, L)),
path([Start|L], P, X, Goal).
The first clause is here to terminate the recursion. Once the Start and Goal arguments are the same as you had noted, the recursion should be over. When using an accumulator this means that we unify the accumulator with the output argument. However, the accumulator contains the answer reversed (and lacks the final goal), so we have reverse([Goal|L], P).
The second clause is very similar to what you had written, with the exception that we now need to pass P as is to the recursive clause. Note that I have removed your disjunction in that clause, it isn't needed in that case.
The complete code:
path(P, Start, Goal) :-
path([], P, Start, Goal).
path(L, P, Goal, Goal) :-
reverse([Goal|L], P).
path(L, P, Start, Goal) :-
adjacent(Start, X),
\+ (memberchk(X, L)),
path([Start|L], P, X, Goal).
I solved my problem. The solution relies on:
Keeping track of visited nodes
When recursing, recursing on a smaller list
Checking if something is not a member of a list to prevent unification when not wanted
My code is as follows:
connected(X,Y) :- adjacent(X,Y);adjacent(Y,X).
not_member(_, []).
not_member(X, [Head|Tail]) :- X \== Head, not_member(X, Tail).
path(P,A,B):-path_helper(P,A,B,[Start]).
path_helper([X,Y],X,Y,_):-connected(X,Y).
path_helper([Goal],Goal,Goal,_).
path_helper([Start|[Head|P]],Start,Goal,Visited):-connected(Start,Head),not_member(Head,Visited),path_helper([Head|P],Head,Goal,[Head|Visited]).

gprolog difference list with duplicate

i have to get list difference between two integer list (both ordinate).
i white this:
difference(L,[],L) :- !.
difference([],_,[]) :- !.
difference([],[],W).
difference([H|T1],[D|T2],T3) :- difference(T1,[D|T2],[H|T3]).
difference([H|T1],[H|T2],T3) :- difference(T1,T2,T3).
but why i can't get my list difference?
if i write this:
difference([],[],W):- write(X).
and this example:
| ?- difference([1,4,4],[1,4],R).
[4|_27]
it makes right!
NB if i have duplicate number i have to show it!
I find your code rather odd. For instance, your third clause: what's W for? Seems like you mean to say:
difference([],[],_).
Second problem: in the fourth clause, there's nothing stopping H and D from being independent variables with the same binding. I suspect you mean something like this:
difference([H|T1],[D|T2],T3) :- H \= D, difference(T1,[D|T2],[H|T3]).
Fixing these things seems to fix the predicate to give a reasonable looking answer:
| ?- difference([1,4,4], [1,4], R).
R = [4]
I think your first several clauses are trying to handle different sorts of base cases, is that right? E.g.:
difference(L, [], L) % handles the case where the second list is exhausted
difference([], _, []) % handles the case where the first list is exhausted
difference([], [], W) % handles the case where the lists are exhausted at the same time
One problem with this is that L = [] is a legitimate binding, so the first and third clauses mean the same thing. You can probably safely remove the third one, because it would have matched and produced the same answer on the first. The second clause is more interesting, because it seems to say that regardless of whatever work we've done so far, if the first list is empty, the result is empty. I find that possibility a bit jarring--is it possible you actually want these two base cases? :
difference([], L, L).
difference(L, [], L).
I remain unconvinced, but until I have a better idea what you're trying to accomplish I may not be able to help more. For instance, what should happen with difference([1, 4], [1, 4, 4], R)? I posit you probably want R = [4], but your code will produce R = [].
Also, I find it unlikely that
difference([],[],W):- write(X).
is going to be a helpful debugging strategy, because Prolog will generate a new variable binding for X because there's nothing for it to refer to.
The final version I have with all my changes looks like this:
difference(L, [], L) :- !.
difference([], L, L) :- !.
difference([H|T1], [D|T2], T3) :- D \= H, difference(T1, [D|T2], [H|T3]).
difference([H|T1], [H|T2], T3) :- difference(T1, T2, T3).
Edit: does this implement your requirements?
not_in1(X, Left, Right) :- member(X, Left), \+ member(X, Right).
not_in(X, Left, Right) :- not_in1(X, Left, Right).
not_in(X, Left, Right) :- not_in1(X, Right, Left).
differences(Left, Right, Differences) :-
findall(X, not_in(X, Left, Right), Differences).
?- differences([1,2,3,4], [1,3,5], X).
X = [2,4,5]
If so, I'll try to get your original code to produce answers that match.
Edit 2: OK, so the problem with the solution above is that it is O(N^2). In the worst case (two totally distinct lists) it will have to compare every item from list 1 to every item of list 2. It's not exploiting the fact that both lists are ordered (I believe that's what you mean by 'ordinate').
The result looks a lot more like your original code, but your original code is not taking advantage of the fact that the items are ordered. This is why the fourth and fifth cases are confusing looking: you should recur down one of the lists or the other depending on which number is larger. The corrected code looks like this:
differences([], Result, Result).
differences(Result, [], Result).
differences([H|Ls], [H|Rs], Result) :- differences(Ls, Rs, Result).
differences([L|Ls], [R|Rs], [L|Result]) :-
L < R,
differences(Ls, [R|Rs], Result).
differences([L|Ls], [R|Rs], [R|Result]) :-
L > R,
differences([L|Ls], Rs, Result).
You can see this produces the same result as the O(N^2) method:
?- differences([1,2,3,4], [1,3,5], X).
X = [2,4,5]
You were right, you do need both base cases. This is so the remainder of either list becomes part of the result. Presumably these will be the largest values ([5] in the example).
Now I have three inductive cases: one for <, one for > and one for =. The equality case is intuitive: recur on both lists, discarding the head of both lists. The next case basically says if the left head is less than the right head, add it to the result and recur on the left's tail. The right is unchanged in that case. The other case is the mirror of this case.
Hope this helps!

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