warplan.pl

loading
details
attribute value
description
owner Johannes Waldmann
uploaded 2017-08-17 03:45:08.0
disk size 5.74 KB
downloadable true
type
attribute value
name no_type
processor id 1
description this is the default benchmark type for rejected benchmarks and benchmarks that are not associated with a type.
owning community none
loading contents
%query: plans(i,i).

%------------------------------------------------------------------------------
%	Benchmark Program - (war) plan for robot control
%
%	by D.H.D Warren
%	Date: 
%
%	To test: try test1. test2. test3. or test4.
%------------------------------------------------------------------------------

:- op(700,xfy,'!!').
:- op(800,xfy,'##').
:- op(900,yfx,::).
%:- entry(plans(g,g)).

plans(C,_) :- not(consistent(C,true)), !, nl, write('impossible'), nl.
plans(C,T) :- time(M0), plan(C,true,T,T1), time(M1), nl, output(T1), nl,
   Time is (M1-M0)/1000, write(Time), write(' secs.'), nl.

time(T) :- statistics(runtime,[T,_]).

output(T::U) :- !, output1(T), write(U), write('.'), nl.
output(T) :- write(T), write('.'), nl.

output1(T'!!'U) :- !, output1(T), write(U), write(';'), nl.
output1(T) :- write(T), write(';'), nl.

plan(X'##'C,P,T,T2) :- !, solve(X,P,T,P1,T1), plan(C,P1,T1,T2).
plan(X,P,T,T1) :- solve(X,P,T,_,T1).

solve(X,P,T,P,T) :- always(X).
solve(X,P,T,P1,T) :- holds(X,T), and(X,P,P1).
solve(X,P,T,X'##'P,T1) :- add(X,U), achieve(X,U,P,T,T1).

achieve(_,U,P,T,T1::U ) :- 
   preserves(U,P),
   can(U,C),
   consistent(C,P),
   plan(C,P,T,T1),
   preserves(U,P).
achieve(X,U,P,T::V,T1::V) :- 
   preserved(X,V),
   retrace(P,V,P1),
   achieve(X,U,P1,T,T1),
   preserved(X,V).

holds(X,_::V) :- add(X,V).
holds(X,T::V) :- !, 
   preserved(X,V),
   holds(X,T),
   preserved(X,V).
holds(X,T) :- given(T,X).

preserved(X,V) :- mkground(X'##'V,0,_), del(X,V), !, fail.
preserved(_,_).

preserves(U,X'##'C) :- preserved(X,U), preserves(U,C).
preserves(_,true).

retrace(P,V,P2) :- 
   can(V,C),
   retrace1(P,V,C,P1),
   conjoin(C,P1,P2).

retrace1(X'##'P,V,C,P1) :- add(Y,V), equiv(X,Y), !, retrace1(P,V,C,P1).
retrace1(X'##'P,V,C,P1) :- elem(Y,C), equiv(X,Y), !, retrace1(P,V,C,P1).
retrace1(X'##'P,V,C,X'##'P1) :- retrace1(P,V,C,P1).
retrace1(true,_,_,true).

consistent(C,P) :- 
   mkground(C'##'P,0,_),
   imposs(S),
   not(not(intersect(C,S))),
   implied(S,C'##'P), 
   !, fail.
consistent(_,_).

and(X,P,P) :- elem(Y,P), equiv(X,Y), !.
and(X,P,X'##'P).

conjoin(X'##'C,P,X'##'P1) :- !, conjoin(C,P,P1).
conjoin(X,P,X'##'P).

elem(X,Y'##'_) :- elem(X,Y).
elem(X,_'##'C) :- !, elem(X,C).
elem(X,X).

intersect(S1,S2) :- elem(X,S1), elem(X,S2).

implied(S1'##'S2,C) :- !, implied(S1,C), implied(S2,C).
implied(X,C) :- elem(X,C).
%% implied(X,_) :- call(X).

notequal(X,Y) :- 
   not(X=Y),
   not(X=qqq(_)),
   not(Y=qqq(_)).

equiv(X,Y) :- not(nonequiv(X,Y)).
popout

content may be truncated. 'popout' for larger text window.

actions get anonymous link download benchmark