Prolog Action Planner Out Of Local Stack Error - prolog

I am trying to implement a kind of planner that to a given integer N generates X possible plans with N actions. A action has conditions and restrictions that must be fulfilled, and a list of effects that will be applied to the current state. I implemented the predicates that check the restrictions and conditions and the one that applies the effects. This method that i created already generates a plan with the N actions, but when i press ";" in swi-prolog to see other results, i get the following error:
ERROR: Out of local stack
This is my code:
makePlan(0,_,List):- List = [].
makePlan(N,I,R):- makeSinglePlan(N,I,R).
makeSinglePlan(0, _ ,_).
makeSinglePlan(N,I,[X|LIST]):-
accao(nome : X, condicoes : Y, efeitos : Z, restricoes : W),
checkAllConditions(Y, I),
checkRestrictions(W),
applyEffects(I, Z, Current),
decrement(N, B),
list_to_set(Current, NC),
makeSinglePlan(B,NC,LIST).
decrement(N,B):- B is N-1.
This is how i call the predicate from the console, the first param is the integer N that represents the number of actions that the plans should have, the second is the initial state, and third the return value:
makePlan(2, [clear(b),on(b,a),on(a,mesa),clear(d),on(d,c),on(c,mesa)], R).ยด
Example of an action:
accao(nome : putOn(X,Y), %name
condicoes : [on(X,Z),clear(X),clear(Y)], %conditions
efeitos : [clear(Z),on(X,Y),-on(X,Z),clear(b)], %effects
restricoes : [(Y\==mesa),(X\==Y),(X\==Z),(Y\==Z)]) %restrictions
Auxiliar Predicates:
% 1 - conditions to be checked 2 - current state
checkAllConditions([],_).
checkAllConditions([X|T],L):- checkCond(X,L) , checkAllConditions(T,L) .
checkCond(X,[X|_]).
checkCond(X,[_|T]):-checkCond(X,T).
% 1 - restrictions to be checked
checkRestrictions([]).
checkRestrictions([X|T]):- X, checkRestrictions(T).
% 1 -current state 2 - effects to be applied 3 - result
applyEffects(L,[],L).
applyEffects(L, [-X|YTail], A):- ! ,remove(X, L, B), applyEffects(B,YTail, A).
applyEffects(L, [Y|YTail], A):- insert(Y, L, B), applyEffects(B,YTail, A).
insert(E, L1, [E|L1] ).
remove(_,[],[]).
remove(X, [X|L1], A):- !, remove(X,L1,A).
remove(X, [Y|L1], [Y|A]):- remove(X,L1,A).

Two changes are necessary:
makeSinglePlan(0, _ ,[]).
makeSinglePlan(N,I,[X|LIST]):-
N > 0,
....
The list of actions should end with [], and the rule only applies for N > 0.
?- makePlan(2, [clear(b),on(b,a),on(a,mesa),clear(d),on(d,c),on(c,mesa)], R).
R = [putOn(b, d), putOn(b, a)]
; R = [putOn(b, d), putOn(a, b)]
; R = [putOn(b, d), putOn(a, d)]
; R = [putOn(b, d), putOn(d, b)]
; R = [putOn(b, d), putOn(d, a)]
; R = [putOn(d, b), putOn(d, c)]
; R = [putOn(d, b), putOn(b, c)]
; R = [putOn(d, b), putOn(b, d)]
; R = [putOn(d, b), putOn(c, b)]
; R = [putOn(d, b), putOn(c, d)]
; false.

Related

Incorrect output when trying to query in a depth first search implementation for prolog

I just can't seem to get the correct output - I am supposed to get -
?- dfs([a], X).
X = [a, f, i] ;
false.
But I get -
?- dfs([a], X).
X = [a|f] ;
% Representation of a tree
% choose initial state a
arc(a, b).
arc(a, f).
arc(b, c).
arc(b, d).
arc(b, e).
arc(f, g).
arc(f, i).
arc(i, j).
arc(i, k).
% the goal
goal(i).
dfs([Node|_], [Node|X]) :-
goal(X).
dfs([Node|_], [Node|X]) :-
expands([Node|_], NewNode),
append([Node|_], NewNode, appendedN),
dfs(appendedN, X).
% expands(+Path, ?NewNode).
% -- Path: is a list of nodes of the form Path=[Node|Nodes], where
% Node is the node we want to expand and Nodes is a list
% of remaining nodes already expanded and containing the root.
% -- NewNode: is a constant representing the node we want to go to,
% as there is an link to it from where we are currently.
%
expands([Node|_], NewNode):-
arc(Node, NewNode).
Your program matches the first clause, dfs([Node|_], [Node|X]), and nothing else, producing X = [a|i] .
Here's a working version.
% Representation of a tree
% choose initial state a
arc(a, b).
arc(a, f).
arc(b, c).
arc(b, d).
arc(b, e).
arc(f, g).
arc(f, i).
arc(i, j).
arc(i, k).
% the goal
goal(i).
% You can expand a starting symbol S to a list L if G is your goal, S expands
% to G in list L1, and you append the two lists.
dfs([S], L) :-
goal(G),
expands(S, G, L1),
append([S], L1, L).
% X expands to Y in list [Y] if there's a direct arc from X to Y (base case).
expands(X, Y, [Y]) :-
arc(X, Y).
% X expands to Z in list [Y|L] if there's a direct arc from X to Y and Y
% expands to Z in list L (recursive case).
expands(X, Z, [Y|L]) :-
arc(X, Y),
expands(Y, Z, L).
In this version, expands() produces all of the lists that start with a:
?- expands(a, X, L).
X = b,
L = [b] ;
X = f,
L = [f] ;
X = c,
L = [b, c] ;
X = d,
L = [b, d] ;
X = e,
L = [b, e] ;
X = g,
L = [f, g] ;
X = i,
L = [f, i] ;
X = j,
L = [f, i, j] ;
X = k,
L = [f, i, k] ;
false.
Then dfs() confirms that the goal i has been reached and adds the start symbol a to the head of the list:
?- dfs([a], X).
X = [a, f, i] ;
false.

How to code a program in prolog, that does comparison on graphs

I'm trying to code a program in prolog that says true if all the paths from a to b are the same size. Example : we have a path from a to b and another from a to c to b, here it's false because there are two paths from a to b with different sizes, the first is 1 and the other is 2. They all must be the same size otherwise it's false.
I started doing this to get the length of each path, but I'm stuck here, I just need to compare if there are two same paths or not, if yes then we compare the two results if they are the same length then true otherwise false, but I don't know how to do it in Prolog :
chemin1(X, Y):-
arete(X,Y).
chemin1(X, Y):-
arete(X,Z),
chemin1(Z,Y).
chemin2(X, Y, N):-
arete(X, Y),
N is 1.
chemin2(X, Y, N):-
arete(X, Z),
N1 is 1,
chemin2(Z, Y, N2),
N is N1+N2.
I'm assuming you have an acyclic directed graph and that a path is represented by a vertex list.
% b
% / \
% a d
% \ / \
% c---e
arete(a, b).
arete(a, c).
arete(b, d).
arete(c, d).
arete(c, e).
arete(d, e).
chemin(X, X, [X]).
chemin(X, Z, [X|Xs]):- arete(X, Y), chemin(Y, Z, Xs).
Examples:
?- chemin(a, d, C).
C = [a, b, d] ;
C = [a, c, d] ;
false.
?- chemin(a, e, C).
C = [a, b, d, e] ;
C = [a, c, d, e] ;
C = [a, c, e] ;
false.
Then, all paths between two vertices X and Y are of the same size, if there are no two paths between vertices X and Y that are of different sizes.
% all_same_size(+X, +Y)
all_same_size(X, Y) :-
not( ( chemin(X, Y, Xs),
chemin(X, Y, Ys),
not( same_size(Xs, Ys) ) ) ).
same_size([], []).
same_size([_|Xs], [_|Ys]) :- same_size(Xs, Ys).
Examples:
?- all_same_size(a, d).
true.
?- all_same_size(a, e).
false.
chemin2(X0,X, N) :-
path(arete, Path, X0,X),
length(Path, N).
allequallength(X0, X) :-
setof(N, chemin2(X0,X, N), [_]).
Using path/4.
With this definition you can also ask a more general question using the facts you indicated:
arete(a, b).
arete(b, d).
arete(b, c).
arete(a, c).
?- allequallength(X0,X).
X0 = X
; X0 = a, X = b
; X0 = a, X = d
; X0 = b, X = c
; X0 = b, X = d.

nesting depth of a term

I'm trying to write a predicate to find the depth of nesting in a prolog term.
for example : for an atom or variable the depth is zero.
for f(a,b,1,2) the depth is 1.
for f(a,b(7,a),1,2) the depth is 2, etc.
here is what I have so far.
% base cases.
get_depth(Term,0):-
non_compound(Term),!.
get_depth(Term,1):-
Term =.. [_|T],
all_basic(T),!. % no compound terms in list.
get_depth(Term,Depth):-
% this is where I need help.
% helper prdeicates
all_basic([T]):-
non_compound(T),!.
all_basic([H|T]):-
non_compound(H),
all_basic(T).
% term is non compound, either atomic or non instantiated variable.
non_compound(Term):-
atomic(Term),!;
var(Term).
max(X,Y,X):-
X >= Y,!.
max(_,Y,Y).
depth(Term, D) :-
Term =.. [_|Args],
( Args = []
-> D = 0
; maplist(depth, Args, Ds),
max_list(Ds, D1), D is D1 + 1
).
If you do not want maplist and max_list
depth(Term, D) :-
Term =.. [_|Args],
( Args = []
-> D = 0
; max_depth(Args, D1), D is D1 + 1
).
max_depth([Term], Max) :- depth(Term, Max).
max_depth([T1, T2| Rest], Max) :-
depth(T1, D1), max_depth([T2 | Rest], M1),
(D1 > M1 -> Max = D1; Max = M1).

how to convert -> into clauses in prolog

So I am working on a practice problem, where I need to find the number of cells with opening right, up , down and left. I have a working solution but I want to change it into clauses. I don't want to to use -> to define if and else. how can I fix the code below without the affecting the solution.
Here is the code:
stats(U,D,L,R) :- maze(Size,_,_,_,_),
findall(R, genXY(Size,R), Out),
statsHelp(Out,U, L, R, D).
statsHelp([],0,0,0,0).
statsHelp([[X|[Y]]|Tl],U, L, R, D) :- cell(X,Y,Dirs,Wt),
(contains1(u,Dirs) -> U1 is 1; U1 is 0), % how do i remove -> and separate them into clauses?
(contains1(d,Dirs) -> D1 is 1; D1 is 0),
(contains1(l,Dirs) -> L1 is 1; L1 is 0),
(contains1(r,Dirs) -> R1 is 1; R1 is 0),
statsHelp(Tl,U2, L2, R2, D2),
U is U1 + U2,
D is D1 + D2,
R is R1 + R2,
L is L1 + L2.
contains1(V,[V|Tl]).
contains1(V,[Hd|Tl]):-
contains1(V,Tl).
Note that your contains1/2 predicate is just the standard member/2, which you could use instead.
As for a version that always succeeds and produces an extra 0 or 1, I think you have to use a cut or negation to achieve that. Here is one with negation:
member_reified(X, Xs, Result) :-
member(X, Xs),
Result = 1.
member_reified(X, Xs, Result) :-
\+ member(X, Xs),
Result = 0.
You could of course also just move your use of -> into your definition of member_reified/3. Different implementations can give different trade-offs on backtracking; this one may succeed several times:
?- member_reified(x, [a, b, c], Result).
Result = 0.
?- member_reified(a, [a, b, c], Result).
Result = 1 ;
false.
?- member_reified(a, [a, b, c, a], Result).
Result = 1 ;
Result = 1 ;
false.

Pairing 2 Dictionaries in Prolog

I need to implement dictionary pairing in prolog. This is what I've done:
pp((A, B), (B,C), RES) :-
RES = [(A,C)].
pp((A, AA),[B|BS], RES) :-
pp((A, AA), B, RES1),
pp((A, AA), BS, RES2),
append(RES1, RES2, RES).
pp([A|AS], [B|BS], C) :-
pp(A, [B|BS], RES1),
pp(AS, [B|BS], RES2),
append(RES1, RES2, RES),
list_to_set(RES, C).
pp(_, _, C) :-
C = [].
Output:
?- pp([(a,b),(b,c)],[(b,c),(c,z)],C).
C = [ (a, c), (b, z)] ;
C = [ (a, c)] ;
C = [ (a, c)] ;
C = [ (a, c)] ;
C = [ (a, c)] ;
C = [ (a, c), (b, z)] ;
C = [ (a, c)] ;
C = [ (a, c)] ;
C = [ (a, c)] ;
C = [ (a, c)] ;
C = [ (b, z)] ;
C = [] ;
C = [] ;
C = [] ;
C = [] ;
C = [ (b, z)] ;
C = [] ;
C = [] ;
C = [] ;
C = [] ;
C = [ (b, z)] ;
C = [] ;
C = [] ;
C = [] ;
C = [] ;
C = [].
?-
The first result is the right answer. The question is why does the predicate pp allow C to be all the other values?
Prolog will try all alternatives it can match, then you get those results as the outcome of unexpected computation going on in your algorithm.
You are 'overloading' pp/3, using it to match both the list and the element.
This make little sense, because your data structure isn't recursive.
Instead of suggesting to put cuts around (a cut commits to done choices, then could help to avoid that spourious results), I think you could get the same result using some builtin, easier to apply than list_to_set/2
pp([],_,[]).
pp([(A,B)|As], X, [(A,C)|R]) :- select((B,C), X, Y), !, pp(As, Y, R).
% BUG ! pp([_|As], X, R) :- select(As, X, R).
pp([_|As], X, R) :- pp(As, X, R).
note the cut after the successful select/3, avoiding the 'skip rule' following.
edit to get more words from the second dictionary, let's retry the successful match:
pp([(A,B)|As], X, [(A,C)|R]) :- select((B,C), X, Y), !, pp([(A,B)|As], Y, R).

Resources