Advertisement
logicmoo

FLUXPLAYER ON SWI

Feb 8th, 2016
250
0
Never
Not a member of Pastebin yet? Sign Up, it unlocks many cool features!
Prolog 49.65 KB | None | 0 0
  1. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  2. %   subsumes_chk(General, Specific)
  3. %   is true when Specific is an instance of General. However, this
  4. %   predicate performs the test without binding any variables neither
  5. %   in General nor in Specific.
  6.  
  7. /*
  8. numbvar(G):-numbervars(G,0,_,[attvar(skip)]).
  9.  
  10. subsumes_chk(General, Specific) :-
  11.     \+((numbvar(Specific),
  12.        \+ (General = Specific)
  13.        )).
  14. */
  15.  
  16. :- [flux_swi].
  17.  
  18. %%% has(1) = has(gold) ; has(2) = has(arrow)
  19.  
  20. %%%
  21. %%% Specify range of cave
  22. %%%
  23.  
  24. xdim(10).
  25. ydim(12).
  26.  
  27. %%%
  28. %%% Specify number of randomly generated pits
  29. %%%
  30.  
  31. no_of_random_pits(12).
  32.  
  33.  
  34. :- [wumpus_simulator].
  35.  
  36. state_update(Z1,enter,Z2,[B,S,G]) :-
  37.   update(Z1,[at(1,1),facing(1)],[],Z2),
  38.   breeze_perception(1,1,B,Z2),
  39.   stench_perception(1,1,S,Z2),
  40.   glitter_perception(1,1,G,Z2).
  41.  
  42. state_update(Z1,exit,Z2,[]) :-
  43.   holds(facing(D),Z1),
  44.   update(Z1,[],[at(1,1),facing(D)],Z2).
  45.  
  46. state_update(Z1,turn,Z2,[]) :-
  47.   holds(facing(D),Z1),
  48.   (D#<4 #/\ D1#=D+1) #\/ (D#=4 #/\ D1#=1),
  49.   update(Z1,[facing(D1)],[facing(D)],Z2).
  50.  
  51. state_update(Z1,grab,Z2,[]) :-
  52.   holds(at(X,Y),Z1),
  53.   update(Z1,[has(1)],[gold(X,Y)],Z2).
  54.  
  55. state_update(Z1,shoot,Z2,[S]) :-
  56.   ( S=true, update(Z1,[dead],[has(2)],Z2)
  57.     ; S=false, update(Z1,[],[has(2)],Z2) ).
  58.  
  59. state_update(Z1,go,Z2,[B,S,G]) :-
  60.   holds(at(X,Y),Z1), holds(facing(D),Z1),
  61.   adjacent(X,Y,D,X1,Y1),
  62.   update(Z1,[at(X1,Y1)],[at(X,Y)],Z2),
  63.   breeze_perception(X1,Y1,B,Z2),
  64.   stench_perception(X1,Y1,S,Z2),
  65.   glitter_perception(X1,Y1,G,Z2).
  66.  
  67. stench_perception(X,Y,Percept,Z) :-
  68.   XE#=X+1, XW#=X-1, YN#=Y+1, YS#=Y-1,
  69.   ( Percept=false, not_holds(wumpus(XE,Y),Z),
  70.                    not_holds(wumpus(XW,Y),Z),
  71.                    not_holds(wumpus(X,YN),Z),
  72.                    not_holds(wumpus(X,YS),Z) ;
  73.     Percept=true,
  74.       or_holds([wumpus(XE,Y),wumpus(X,YN),
  75.                 wumpus(XW,Y),wumpus(X,YS)],Z) ).
  76.  
  77. breeze_perception(X,Y,Percept,Z) :-
  78.   XE#=X+1, XW#=X-1, YN#=Y+1, YS#=Y-1,
  79.   ( Percept=false, not_holds(pit(XE,Y),Z),
  80.                    not_holds(pit(XW,Y),Z),
  81.                    not_holds(pit(X,YN),Z),
  82.                    not_holds(pit(X,YS),Z) ;
  83.     Percept=true,
  84.       or_holds([pit(XE,Y),pit(X,YN),
  85.                 pit(XW,Y),pit(X,YS)],Z) ).
  86.  
  87. glitter_perception(X,Y,Percept,Z) :-
  88.   Percept=false, not_holds(gold(X,Y),Z) ;
  89.   Percept=true,  holds(gold(X,Y),Z).
  90.  
  91. adjacent(X,Y,D,X1,Y1) :-
  92.   xdim(XD), ydim(YD),
  93.   X in 1..XD, X1 in 1..XD, Y in 1..YD, Y1 in 1..YD, D in 1..4,
  94.       (D#=1) #/\ (X1#=X)   #/\ (Y1#=Y+1) % north
  95.   #\/ (D#=3) #/\ (X1#=X)   #/\ (Y1#=Y-1) % south
  96.   #\/ (D#=2) #/\ (X1#=X+1) #/\ (Y1#=Y)   % east
  97.   #\/ (D#=4) #/\ (X1#=X-1) #/\ (Y1#=Y).  % west
  98.  
  99. init(Z0) :- Z0 = [has(2),wumpus(WX,WY)|Z],
  100.             xdim(XD), ydim(YD), XD1 is XD+1, YD1 is YD+1,
  101.             WX in 1..XD, WY in 1..YD,
  102.             not_holds(wumpus(1,1),Z0),
  103.             not_holds_all(wumpus(_,_),Z),
  104.             not_holds(dead,Z),
  105.             not_holds(pit(1,1),Z),
  106.             not_holds_all(pit(_,0),Z), %boundary
  107.             not_holds_all(pit(_,YD1),Z),
  108.             not_holds_all(pit(0,_),Z),
  109.             not_holds_all(pit(XD1,_),Z),
  110.             not_holds_all(at(_,_),Z),
  111.             not_holds_all(facing(_),Z),
  112.             duplicate_free(Z0).
  113.  
  114. main :- init_simulator,
  115.         init(Z0), execute(enter,Z0,Z1),
  116.         Cpts=[1,1,[1,2]], Vis=[[1,1]], Btr=[],
  117.         main_loop(Cpts,Vis,Btr,Z1).
  118.  
  119. main_loop([X,Y,Choices|Cpts],Vis,Btr,Z) :-
  120.   Choices=[Dir|Dirs] ->
  121.     (explore(X,Y,Dir,Vis,Z,Z1) ->
  122.        knows_val([X1,Y1],at(X1,Y1),Z1),
  123.        hunt_wumpus(X1,Y1,Z1,Z2),
  124.        (knows(gold(X1,Y1),Z2) ->
  125.           execute(grab,Z2,Z3), go_home(Z3)
  126.         ; Cpts1=[X1,Y1,[1,2,3,4],X,Y,Dirs|Cpts],
  127.           Vis1=[[X1,Y1]|Vis], Btr1=[X,Y|Btr],
  128.           main_loop(Cpts1,Vis1,Btr1,Z2) )
  129.      ; main_loop([X,Y,Dirs|Cpts],Vis,Btr,Z) )
  130.   ; backtrack(Cpts,Vis,Btr,Z).
  131.  
  132. explore(X,Y,D,V,Z1,Z2) :-
  133.   adjacent(X,Y,D,X1,Y1), \+ member([X1,Y1],V),
  134.   knows_not(pit(X1,Y1),Z1),
  135.   (knows_not(wumpus(X1,Y1),Z1);knows(dead,Z1)),
  136.   turn_to(D,Z1,Z), execute(go,Z,Z2).
  137.  
  138. backtrack(_,_,[],Z) :- execute(exit,Z,_).
  139. backtrack(Cpts,Vis,[X,Y|Btr],Z) :-
  140.   go_back(X,Y,Z,Z1), main_loop(Cpts,Vis,Btr,Z1).
  141.  
  142. go_back(X,Y,Z1,Z2) :-
  143.   holds(at(X1,Y1),Z1), adjacent(X1,Y1,D,X,Y),
  144.   turn_to(D,Z1,Z), execute(go,Z,Z2).
  145.  
  146. turn_to(D,Z1,Z2) :-
  147.   knows(facing(D),Z1) -> Z2=Z1
  148.   ; execute(turn,Z1,Z), turn_to(D,Z,Z2).
  149.  
  150. hunt_wumpus(X,Y,Z1,Z2) :-
  151.   \+ knows(dead,Z1),
  152.   knows_val([WX,WY],wumpus(WX,WY),Z1),
  153.   in_direction(X,Y,D,WX,WY)
  154.   -> turn_to(D,Z1,Z), execute(shoot,Z,Z2)
  155.    ; Z2=Z1.
  156.  
  157. in_direction(X,Y,D,X1,Y1) :-
  158.   xdim(XD), ydim(YD),
  159.   X in 1..XD, X1 in 1..XD, Y in 1..YD, Y1 in 1..YD, D in 1..4,
  160.       (D#=1) #/\ (X1#=X) #/\ (Y1#>Y)  % north
  161.   #\/ (D#=3) #/\ (X1#=X) #/\ (Y1#<Y)  % south
  162.   #\/ (D#=2) #/\ (X1#>X) #/\ (Y1#=Y)  % east
  163.   #\/ (D#=4) #/\ (X1#<X) #/\ (Y1#=Y). % west
  164.  
  165. go_home(Z) :- write('Planning...'),
  166.               a_star_plan(Z,S), execute(S,Z,Z1), execute(exit,Z1,_).
  167.  
  168. %%
  169. %% a_star_plan(Z,S)
  170. %%
  171. %% use A* planning to find situation S representing the shortest path to (1,1)
  172. %%
  173.  
  174. :- dynamic visited/2.
  175.  
  176. a_star_plan(Z,S) :-
  177.    retractall(visited(_,_)),
  178.    knows_val([X,Y],at(X,Y),Z), assertz(visited(X,Y)),
  179.    a_star(Z,[[],0,100000],S).
  180.  
  181. a_star(Z,[Sit,Cost,_|L],S) :-
  182.    findall([A,H], a_star_do(Z,Sit,A,H), Actions),
  183.    ( member([Action,0], Actions) -> S=do(Action,Sit)
  184.      ;
  185.      insert_all(Actions, Sit, Cost, L, L1),
  186.      a_star(Z, L1, S) ).
  187.  
  188. insert_all([],_,_,L,L).
  189.  
  190. insert_all([[A,H]|As],S,C,L,L2) :-
  191.    insert_all(As,S,C,L,L1),
  192.    Cost is C+1, Heuristic is Cost+H,
  193.    ins(do(A,S),Cost,Heuristic,L1,L2).
  194.  
  195. ins(S1,C1,H1,[S2,C2,H2|L],L2) :-
  196.    ( H1>H2 -> ins(S1,C1,H1,L,L1), L2=[S2,C2,H2|L1]
  197.      ;
  198.      L2=[S1,C1,H1,S2,C2,H2|L] ).
  199.  
  200. ins(S,C,H,[],[S,C,H]).
  201.  
  202. a_star_do(Z,S,A,H) :-
  203.   ( S=do(go_to(X,Y),_) -> true ; knows_val([X,Y],at(X,Y),Z) ),
  204.   ( D=4 ; D=3 ; D=2 ; D=1 ),
  205.   adjacent(X,Y,D,X1,Y1), \+ visited(X1,Y1),
  206.   knows_not(pit(X1,Y1),Z),
  207.   ( \+ knows(dead,Z)->knows_not(wumpus(X1,Y1),Z)
  208.     ; true ),
  209.   A = go_to(X1,Y1),
  210.   assertz(visited(X1,Y1)),
  211.   H is X1+Y1-2.
  212.  
  213. complex_action(do(A,S),Z1,Z2) :-
  214.   execute(S,Z1,Z), execute(A,Z,Z2).
  215.  
  216. complex_action(go_to(X,Y),Z1,Z2) :-
  217.   holds(at(X1,Y1),Z1), adjacent(X1,Y1,D,X,Y),
  218.   turn_to(D,Z1,Z), execute(go,Z,Z2).
  219.  
  220.  
  221.  
  222.  
  223. :- use_module(library(terms)).
  224. :- use_module(library(varnumbers)).
  225.  
  226. :- use_module( library(random)).
  227.  
  228. :- dynamic current_state/1.
  229.  
  230. init_simulator :- init_scenario,
  231.                   retractall(current_state(_)), assertz(current_state([])).
  232.  
  233. :- dynamic wumpus/2,pit/2,gold/2.
  234.  
  235. init_scenario :-
  236.  
  237.    retractall(wumpus(_,_)), retractall(pit(_,_)), retractall(gold(_,_)),
  238.  
  239.    xdim(XD), ydim(YD),
  240.  
  241.    random(0,4294967296,N1), random(0,4294967296,N2), XW is N1 mod XD + 1, YW is N2 mod YD + 1,
  242.    ( XW=1, YW=1 -> true ; assertz(wumpus(XW,YW)), write(wumpus(XW,YW)) ),
  243.  
  244.    random(0,4294967296,N3), random(0,4294967296,N4), XG is N3 mod XD + 1, YG is N4 mod YD + 1,
  245.    assertz(gold(XG,YG)), write(gold(XG,YG)),
  246.  
  247.    no_of_random_pits(P), create_pits(P).
  248.  
  249. create_pits(0) :- !.
  250. create_pits(M) :-
  251.    xdim(XD), ydim(YD),
  252.    random(0,4294967296,N1), random(0,4294967296,N2), XP is N1 mod XD + 1, YP is N2 mod YD + 1,
  253.    ( XP+YP < 4 -> create_pits(M) ; assertz(pit(XP,YP)), write(pit(XP,YP)) ),
  254.    M1 is M-1, create_pits(M1).
  255.  
  256.  
  257. perform(turn, []) :-
  258.         write('turn'), nl,
  259.         current_state([at(X,Y),facing(D)]),
  260.         retract(current_state([at(X,Y),facing(D)])),
  261.         ( D < 4 -> D1 is D+1 ; D1 is 1 ),
  262.         assertz(current_state([at(X,Y),facing(D1)])).
  263.  
  264. perform(enter, [Breeze,Stench,Glitter]) :-
  265.         write('enter'), nl,
  266.         current_state(Z),
  267.         retract(current_state(Z)),
  268.         assertz(current_state([at(1,1),facing(1)])),
  269.         ( gold(1,1) -> Glitter = true ; Glitter = false ),
  270.         ( (wumpus(1,2) ; wumpus(2,1)) -> Stench = true ;
  271.             Stench = false ),
  272.         ( (pit(2,1) ; pit(1,2)) -> Breeze = true ;
  273.             Breeze = false ).
  274.  
  275. perform(exit, []) :-
  276.         write('exit'), nl,
  277.         current_state([at(X,Y),facing(D)]),
  278.         retract(current_state([at(X,Y),facing(D)])),
  279.         assertz(current_state([])).
  280.  
  281. perform(grab, []) :-
  282.         write('grab'), nl.
  283.  
  284. perform(shoot, [Scream]) :-
  285.         write('shoot'), nl,
  286.         current_state([at(X,Y),facing(D)]),
  287.         wumpus(WX, WY),
  288.         ( in_direction(X, Y, D, WX, WY), Scream = true ; Scream = false ).
  289.  
  290. perform(go, [Breeze,Stench,Glitter]) :-
  291.         write('go'), nl,
  292.         current_state([at(X,Y),facing(D)]),
  293.         retract(current_state([at(X,Y),facing(D)])),
  294.         ( D = 1 -> X1 is X, Y1 is Y+1 ;
  295.           D = 3 -> X1 is X, Y1 is Y-1 ;
  296.           D = 2 -> X1 is X+1, Y1 is Y ;
  297.           D = 4 -> X1 is X-1, Y1 is Y ),
  298.         assertz(current_state([at(X1,Y1),facing(D)])),
  299.         ( gold(X1,Y1) -> Glitter = true ; Glitter = false ),
  300.         X_east is X1+1, X_west is X1-1, Y_north is Y1+1, Y_south is Y1-1,
  301.         ( (wumpus(X_east,Y1) ; wumpus(X1,Y_north) ;
  302.            wumpus(X_west,Y1) ; wumpus(X1,Y_south)) -> Stench = true ;
  303.             Stench = false ),
  304.         ( (pit(X_east,Y1) ; pit(X1,Y_north) ;
  305.            pit(X_west,Y1) ; pit(X1,Y_south)) -> Breeze = true ;
  306.             Breeze = false ).
  307.  
  308.  
  309.  
  310.  
  311.  
  312. %% fluent.chr - CHR for SWI-Prolog
  313.  
  314. %% $Id: fluent.chr, v 2.0 NOW $
  315. %%
  316. %% FLUX: a Prolog library for high-level programming of cognitive agents
  317. %% Copyright 2003, 2004  Michael Thielscher
  318. %% This file belongs to the flux kernel package distributed at
  319. %%   http://www.fluxagent.org
  320. %%
  321. %% This library is free software; you can redistribute it and/or modify it
  322. %% under the terms of the GNU Library General Public License as published by
  323. %% the Free Software Foundation; either version 2 of the License, or (at your
  324. %% option) any later version.
  325. %%
  326. %% This library is distributed in the hope that it will be useful, but WITHOUT
  327. %% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
  328. %% FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Library General Public
  329. %% License for more details.
  330. %%
  331. %% You should have received a copy of the GNU Library General Public License
  332. %% along with this library; if not, write to the Free Software Foundation,
  333. %% Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
  334. %%
  335. %% Consult the file COPYING for license details.
  336.  
  337. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  338. %%
  339. %% Preamble
  340. %%
  341. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  342.  
  343.  
  344. % handler fluent.
  345.  
  346. :- chr_constraint not_holds/2, not_holds_all/2, duplicate_free/1,
  347.             or_holds/2, or_holds/3, cancel/2, cancelled/2.
  348.  
  349. :- chr_option(check_guard_bindings,off).
  350.  
  351. :- make,check,autoload.
  352. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  353. %%
  354. %% Constraint Handling Rules for state constraints
  355. %%
  356. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  357.  
  358.  
  359. not_holds(F, [F1|Z]) <=> neq(F, F1), not_holds(F, Z).
  360. not_holds(_, [])     <=> true.
  361.  
  362. not_holds_all(F, [F1|Z]) <=> neq_all(F, F1), not_holds_all(F, Z).
  363. not_holds_all(_, [])     <=> true.
  364.  
  365. not_holds_all(F, Z) \ not_holds(G, Z)     <=> inst(G, F) | true.
  366. not_holds_all(F, Z) \ not_holds_all(G, Z) <=> inst(G, F) | true.
  367.  
  368. duplicate_free([F|Z]) <=> not_holds(F,Z), duplicate_free(Z).
  369. duplicate_free([])    <=> true.
  370.  
  371. or_holds([F],Z) <=> F\=eq(_,_) | holds(F,Z).
  372.  
  373. or_holds(V,_Z) <=> \+ ( member(F,V),F\=eq(_,_) ) | or_and_eq(V,D), call(D).
  374.  
  375. or_holds(V,[]) <=> member(F, V, W), F\=eq(_,_) | or_holds(W,[]).
  376.  
  377. or_holds(V,_Z) <=> member(eq(X,Y),V), or_neq(exists,X,Y,D), \+ call(D) | true.
  378. or_holds(V,Z) <=> member(eq(X,Y),V,W), \+ (and_eq(X,Y,D), call(D)) | or_holds(W,Z).
  379.  
  380. not_holds(F, Z) \ or_holds(V, Z) <=> member(G, V, W), F==G | or_holds(W, Z).
  381.  
  382. not_holds_all(F, Z) \ or_holds(V, Z) <=> member(G, V, W), inst(G, F)
  383.                                          | or_holds(W, Z).
  384.  
  385. or_holds(V, [F|Z]) <=> or_holds(V, [], [F|Z]).
  386.  
  387. or_holds([G|V],W,[F|Z]) <=> true | ( G==F -> true ;
  388.                             G\=F -> or_holds(V,[G|W],[F|Z]) ;
  389.                             G=..[_|ArgX], F=..[_|ArgY],
  390.                             or_holds(V,[eq(ArgX,ArgY),G|W],[F|Z])).
  391.  
  392. or_holds([],W,[_|Z]) <=> or_holds(W,Z).
  393.  
  394.  
  395. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  396. %%
  397. %% Constraint Handling Rules for cancellation of constraints on a fluent
  398. %%
  399. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  400.  
  401. cancel(F,Z) \ not_holds(G,Z)     <=> \+ F\=G | true.
  402.  
  403. cancel(F,Z) \ not_holds_all(G,Z) <=> \+ F\=G | true.
  404.  
  405. cancel(F,Z) \ or_holds(V,Z)      <=> member(G,V), \+ F\=G | true.
  406.  
  407. cancel(F,Z), cancelled(F,Z) <=> true.
  408.  
  409.  
  410. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  411. %%
  412. %% Auxiliary clauses
  413. %%
  414. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  415.  
  416. neq(F, F1)     :- or_neq(exists, F, F1).
  417. neq_all(F, F1) :- or_neq(forall, F, F1).
  418.  
  419. or_neq(Q, Fx, Fy) :-
  420.   functor(Fx, F, M), functor(Fy, G, N),
  421.   ( F=G, M=N -> Fx =.. [_|ArgX], Fy =.. [_|ArgY], or_neq(Q, ArgX, ArgY, D), call(D)
  422.               ; true ).
  423.  
  424. or_neq(_, [], [], (0#\=0)).
  425. or_neq(Q, [X|X1], [Y|Y1], D) :-
  426.   or_neq(Q, X1, Y1, D1),
  427.   ( Q=forall, var(X), \+ is_domain(X) -> ( binding(X,X1,Y1,YE) ->
  428.  
  429.                                          D=((Y#\=YE)#\/D1) ; D=D1 )
  430.                                          ; D=((X#\=Y)#\/D1) ).
  431.                                          
  432. binding(X,[X1|ArgX],[Y1|ArgY],Y) :-
  433.    X==X1 -> Y=Y1 ; binding(X,ArgX,ArgY,Y).
  434.  
  435. and_eq([], [], (0#=0)).
  436. and_eq([X|X1], [Y|Y1], D) :-
  437.    and_eq(X1, Y1, D1),
  438.    D = ((X#=Y)#/\D1).
  439.  
  440. or_and_eq([], (0#\=0)).
  441. or_and_eq([eq(X,Y)|Eq], (D1#\/D2)) :-
  442.    and_eq(X,Y,D1),
  443.    or_and_eq(Eq,D2).
  444.  
  445. %% inst checks whether G is an instance of F and if so whether there is no
  446. %% domain variable which is bound to some value in this instance
  447.  
  448. inst(G,F) :- subsumes_chk(F,G), var_chk(G,F).
  449.  
  450. var_chk(X,Y) :- var(Y), X==Y.
  451. var_chk(_,Y) :- var(Y), \+ fd_var(Y).
  452. var_chk(X,Y) :- is_list(Y), var_chk_list(X,Y).
  453. var_chk(X,Y) :- compound(Y), \+ is_list(Y), X=..[_|Xs], Y=..[_|Ys], var_chk_list(Xs,Ys).
  454.  
  455. var_chk_list([],[]).
  456. var_chk_list([X|Xs],[Y|Ys]) :- var_chk(X,Y), var_chk_list(Xs,Ys).
  457.  
  458. member(X, [X|T], T).
  459. member(X, [H|T], [H|T1]) :- member(X, T, T1).
  460.  
  461. is_domain(X) :- fd_var(X), \+ ( fd_max(X,sup), fd_min(X,inf)).
  462. fd_min(X,D):-M #=< X,fd_dom(M,D).
  463. fd_max(X,D):-M #>= X,fd_dom(M,D).
  464.  
  465. %% $Id: flux.pl, v 2.0 2004/01/22 00:58:00 $
  466. %%
  467. %% FLUX: a Prolog library for high-level programming of cognitive agents
  468. %% Copyright 2003, 2004  Michael Thielscher
  469. %% This file belongs to the flux kernel package distributed at
  470. %%   http://www.fluxagent.org
  471. %%
  472. %% This library is free software; you can redistribute it and/or modify it
  473. %% under the terms of the GNU Library General Public License as published by
  474. %% the Free Software Foundation; either version 2 of the License, or (at your
  475. %% option) any later version.
  476. %%
  477. %% This library is distributed in the hope that it will be useful, but WITHOUT
  478. %% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
  479. %% FITNESS FOR A PARTICULAR PURPOSE.  See the GNU Library General Public
  480. %% License for more details.
  481. %%
  482. %% You should have received a copy of the GNU Library General Public License
  483. %% along with this library; if not, write to the Free Software Foundation,
  484. %% Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
  485. %%
  486. %% Consult the file COPYING for license details.
  487.  
  488. :- use_module( library(clpfd)).
  489.  
  490. :- autoload.
  491.  
  492. :- expects_dialect(sicstus).
  493.  
  494. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  495. %%
  496. %% Libraries
  497. %%
  498. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  499.  
  500. %%
  501. %% term utilities (Sicstus library)
  502. %%
  503.  
  504. :- use_module(library(varnumbers)).
  505. :- use_module( library(terms)).
  506.  
  507. %%
  508. %%  List operations (Sicstus library)
  509. %%
  510.  
  511. :- use_module( library(lists)).
  512.  
  513. %%
  514. %% finite domain constraint solver (Sicstus library)
  515. %%
  516.  
  517. %%
  518. %% constraint handling rules (Sicstus library)
  519. %%
  520.  
  521. :- use_module( library(chr)).
  522.  
  523. %%
  524. %% FLUX constraint handling rules
  525. %%
  526.  
  527. :- autoload.
  528.  
  529. :- ['fluent.chr'].
  530.  
  531. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  532. %%
  533. %% State Specifications and Update
  534. %%
  535. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  536.  
  537. %%
  538. %% holds(F,Z)
  539. %%
  540. %% asserts that fluent F holds in state Z
  541. %%
  542. holds(F, [F|_]).
  543. holds(F, Z) :- nonvar(Z), Z=[F1|Z1], F\==F1, holds(F, Z1).
  544.  
  545. %%
  546. %% holds(F,Z,Zp)
  547. %%
  548. %% asserts that fluent F holds in state Z
  549. %%
  550. %% state Zp is Z without F.
  551. %%
  552. holds(F, [F|Z], Z).
  553. holds(F, Z, [F1|Zp]) :- nonvar(Z), Z=[F1|Z1], F\==F1, holds(F, Z1, Zp).
  554.  
  555. %%
  556. %% cancel(F,Z1,Z2)
  557. %%
  558. %% state Z2 is state Z1 with all (positive, negative, disjunctive)
  559. %% knowledge of fluent F canceled
  560. %%
  561. cancel(F,Z1,Z2) :-
  562.    var(Z1)    -> cancel(F,Z1), cancelled(F,Z1), Z2=Z1 ;
  563.    Z1 = [G|Z] -> ( F\=G -> cancel(F,Z,Z3), Z2=[G|Z3]
  564.                          ; cancel(F,Z,Z2) ) ;
  565.    Z1 = []    -> Z2 = [].
  566.  
  567. %%
  568. %% minus(Z1,ThetaN,Z2)
  569. %%
  570. %% state Z2 is state Z1 minus the fluents in list ThetaN
  571. %%
  572. minus_(Z, [], Z).
  573. minus_(Z, [F|Fs], Zp) :-
  574.    ( \+ not_holds(F, Z) -> holds(F, Z, Z1) ;
  575.      \+ holds(F, Z)     -> Z1 = Z
  576.                          ; cancel(F, Z, Z1), not_holds(F, Z1) ),
  577.    minus_(Z1, Fs, Zp).
  578.  
  579. %%
  580. %% plus(Z1,ThetaP,Z2)
  581. %%
  582. %% state Z2 is state Z1 plus the fluents in list ThetaP
  583. %%
  584. plus_(Z, [], Z).
  585. plus_(Z, [F|Fs], Zp) :-
  586.    ( \+ holds(F, Z)     -> Z1=[F|Z] ;
  587.      \+ not_holds(F, Z) -> Z1=Z
  588.                          ; cancel(F, Z, Z2), not_holds(F, Z2), Z1=[F|Z2] ),
  589.    plus_(Z1, Fs, Zp).
  590.  
  591. %%
  592. %% update(Z1,ThetaP,ThetaN,Z2)
  593. %%
  594. %% state Z2 is state Z1 minus the fluents in list ThetaN
  595. %% plus the fluents in list ThetaP
  596. %%
  597. update(Z1, ThetaP, ThetaN, Z2) :-
  598.    minus_(Z1, ThetaN, Z), plus_(Z, ThetaP, Z2).
  599.  
  600.  
  601. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  602. %%
  603. %% State Knowledge
  604. %%
  605. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  606.  
  607. %%
  608. %% knows(F,Z)
  609. %%
  610. %% ground fluent F is known to hold in state Z
  611. %%
  612. knows(F, Z) :- \+ not_holds(F, Z).
  613.  
  614. %%
  615. %% knows_not(F,Z)
  616. %%
  617. %% ground fluent F is known not to hold in state Z
  618. %%
  619. knows_not(F, Z) :- \+ holds(F, Z).
  620.  
  621. %%
  622. %% knows_val(X,F,Z)
  623. %%
  624. %% there is an of the variables in X for which
  625. %% non-ground fluent F is known to hold in state Z
  626. %%
  627. %% Example:
  628. %%
  629. %% ?- knows_val([X], f(X,Y), [f(1,3),f(2,U),f(V,2)|_])
  630. %%
  631. %% X=1 More?
  632. %% X=2 More?
  633. %% No
  634. %%
  635. knows_val(X, F, Z) :- k_holds(F, Z), knows_val(X).
  636.  
  637. k_holds(F, Z) :- nonvar(Z), Z=[F1|Z1],
  638.                  ( instance1(F1, F), F=F1 ; k_holds(F, Z1) ).
  639.  
  640. :- dynamic known_val/1.
  641.  
  642. knows_val(X) :- dom(X), \+ nonground(X), ambiguous(X) -> false.
  643. knows_val(X) :- retract(known_val(X)).
  644.  
  645. dom([]).
  646. dom([X|Xs]) :- dom(Xs), ( is_domain(X) -> indomain(X)
  647.                                         ; true ).
  648.  
  649. ambiguous(X) :- retract(known_val(_)) -> true
  650.                 ;
  651.                 assertz(known_val(X)), false.
  652.  
  653.  
  654. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  655. %%
  656. %% Execution
  657. %%
  658. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  659.  
  660. %%
  661. %% execute(A,Z1,Z2)
  662. %%
  663. %% perform A and update current state Z1 to state Z2
  664. %%
  665. %% It assumes the definition of a predicate perform(A,Y) or perform(A,Y,E),
  666. %% which actually performs primitive action A and returns a list Y of
  667. %% sensing results and, in the ternary variant, a set of exogenous actions E.
  668. %%
  669. %% It also assumes the definition of a predicate state_update(Z1,A,Z2,Y),
  670. %% which specifies the effect of an action A with sensing result Y as
  671. %% update of state Z1 to state Z2. The effects of exogenous actions are assumed
  672. %% to be specified by a predicate state_update(Z1,A,Z2) without sensing result.
  673. %%
  674. %% The clauses for state_update must NOT allow for backtracking for fixed sensor result.
  675. %%
  676. %% For troubleshooting (qualification problem), it is assumed that accidental effects
  677. %% of non-exogenous actions are described by a predicate ab_state_update(Z1,A,Z2,Y).
  678. %% The initial state is assumed to be specified by init(Z0).
  679. %%
  680. %% The clauses for ab_state_update may allow for backtracking.
  681. %%
  682. %% The execution of non-primitive actions A is defined as the predicate
  683. %% complex_action(A,Z1,Z2) such that the final result of doing A in state Z1 is
  684. %% state Z2.
  685. %%
  686. %% A can be a primitive action, a list, a conditional of the form if(F,A1,A2)
  687. %% where F fluent, or the name of a complex action. The clause should be used
  688. %% for non-primitive A only if its executability is guaranteed also in case
  689. %% of possible accidents.
  690. %%
  691. execute(A,Z1,Z2) :-
  692.    current_predicate(perform/2),
  693.    perform(A,Y)    -> ( current_predicate(ab_state_update/4)
  694.                         ->
  695.                            ( Z1=[sit(S)|Z], ! ; S=[], Z=Z1 ),
  696.                            ( state_update(Z,A,Z3,Y)
  697.                              ; ab_res([[A,Y]|S],Z3) ),
  698.                            !, Z2=[sit([[A,Y]|S])|Z3]
  699.                         ;
  700.                         state_update(Z1,A,Z2,Y) ) ;
  701.  
  702.    current_predicate(perform/3),
  703.    perform(A,Y,E)  -> ( current_predicate(ab_state_update/4)
  704.                         ->
  705.                            ( Z1=[sit(S)|Z], ! ; S=[], Z=Z1 ),
  706.                            ( state_update(Z,A,Z3,Y), state_updates(Z3,E,Z4)
  707.                              ; ab_res([[A,Y,E]|S],Z4) ),
  708.                            !, Z2=[sit([[A,Y,E]|S])|Z4]
  709.                         ;
  710.                         state_update(Z1,A,Z,Y), state_updates(Z,E,Z2) ) ;
  711.  
  712.    A = [A1|A2]     ->
  713.                       execute(A1,Z1,Z), execute(A2,Z,Z2) ;
  714.  
  715.    A = if(F,A1,A2) ->
  716.                       (holds(F,Z1) -> execute(A1,Z1,Z2)
  717.                                     ; execute(A2,Z1,Z2)) ;
  718.  
  719.    A = []          ->
  720.                       Z1=Z2 ;
  721.  
  722.    complex_action(A,Z1,Z2).
  723.  
  724. ab_res([],Z) :- init(Z).
  725. ab_res([S1|S],Z) :-
  726.    ab_res(S,Z1),
  727.    ( S1=[A,Y] -> ( state_update(Z1,A,Z,Y) ; ab_state_update(Z1,A,Z,Y) )
  728.      ;
  729.      S1=[A,Y,E], ( state_update(Z1,A,Z2,Y) ; ab_state_update(Z1,A,Z2,Y) ),
  730.                  state_updates(Z2, E, Z) ).
  731.  
  732. state_updates(Z, [], Z).
  733. state_updates(Z1, [A|S], Z2) :-
  734.    state_update(Z1, A, Z), state_updates(Z, S, Z2).
  735.  
  736. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  737. %%
  738. %% Planning
  739. %%
  740. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  741.  
  742. %%
  743. %% plan(PlanningProblemName,Z,P)
  744. %%
  745. %% P is an optimal plan for PlanningProblemName with starting state Z
  746. %%
  747. %% It assumes the definition of a predicate PlanningProblemName(Z0,P,Z)
  748. %% describing the search space such that plan P executed in starting
  749. %% state Z0 results in state Z which satisfies the planning goal,
  750. %% and the definition of plan_cost(PlanningProblemName,P,Z,C) such that
  751. %% C is the cost of plan P resulting in state Z; or
  752. %%
  753. %% the definition of a predicate is PlanningProblemName(Z0,P)
  754. %% describing the search space such that conditional plan P executed in
  755. %% starting state Z0 necessarily results in a state in which the planning
  756. %% goal is satisfied, and the definition of plan_cost(PlanningProblemName,P,C)
  757. %% such that C is the cost of plan P.
  758. %%
  759. %% For the definition of the search space, the predicates for knowledge
  760. %% described below can be used.
  761. %%
  762. :- dynamic plan_search_best/2.
  763.  
  764. plan(Problem, Z, P) :-
  765.    assertz(plan_search_best(_,-1)),
  766.    plan_search(Problem, Z),
  767.    retract(plan_search_best(P,C)),
  768.    C =\= -1.
  769.  
  770. plan_search(Problem, Z) :-
  771.    current_predicate(Problem/2) ->
  772.       ( PlanningProblem =.. [Problem,Z,P],
  773.         call(PlanningProblem),
  774.         plan_cost(Problem, P, C),
  775.         plan_search_best(_,C1),
  776.         ( C1 =< C, C1 =\= -1 -> fail
  777.                               ; retract(plan_search_best(_,C1)),
  778.                                 assertz(plan_search_best(P,C)), fail )
  779.         ;
  780.         true ) ;
  781.    PlanningProblem =.. [Problem,Z,P,Zn],
  782.    call(PlanningProblem),
  783.    plan_cost(Problem, P, Zn, C),
  784.    plan_search_best(_,C1),
  785.    ( C1 =< C, C1 =\= -1 -> fail
  786.                          ; retract(plan_search_best(_,C1)),
  787.                            assertz(plan_search_best(P,C)), fail )
  788.    ;
  789.    true.
  790.  
  791. %%
  792. %% knows(F,S,Z0)
  793. %%
  794. %% ground fluent F is known to hold after doing S in state Z0
  795. %%
  796. %% S ::= [] | do(A,S)
  797. %% A ::= primitive action | if_true(F)| if_false(F)
  798. %% F ::= fluent
  799. %%
  800. knows(F, S, Z0) :- \+ ( res(S, Z0, Z), not_holds(F, Z) ).
  801.  
  802. %%
  803. %% knows_not(F,S,Z0)
  804. %%
  805. %% ground fluent F is known not to hold after doing S in state Z0
  806. %%
  807. knows_not(F, S, Z0) :- \+ ( res(S, Z0, Z), holds(F, Z) ).
  808.  
  809. %%
  810. %% knows_val(X,F,S,Z0)
  811. %%
  812. %% there is an instance of the variables in X for which
  813. %% non-ground fluent F is known to hold after doing S in state Z0
  814. %%
  815. knows_val(X, F, S, Z0) :-
  816.    res(S, Z0, Z) -> findall(X, knows_val(X,F,Z), T),
  817.                     assertz(known_val(T)),
  818.                     false.
  819. knows_val(X, F, S, Z0) :-
  820.    known_val(T), retract(known_val(T)), member(X, T),
  821.    \+ ( res(S, Z0, Z), not_holds_all(F, Z) ).
  822.  
  823. res([], Z0, Z0).
  824. res(do(A,S), Z0, Z) :-
  825.    A = if_true(F)  -> res(S, Z0, Z), holds(F, Z) ;
  826.    A = if_false(F) -> res(S, Z0, Z), not_holds(F, Z) ;
  827.    res(S, Z0, Z1), state_update(Z1, A, Z, _).
  828.  
  829.  
  830. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  831. %%
  832. %% Ramification Problem
  833. %%
  834. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  835.                  
  836. %%
  837. %% causes(Z1,P,N,Z2)
  838. %%
  839. %% state Z2 is the result of applying causal relationships to
  840. %% state Z1 wrt. positive effects P and negative effects N
  841. %%
  842. %% It is assumed that the causal relationships of a domain are specified
  843. %% by clauses for the predicate causes(Z1,P1,N1,Z2,P2,N2) such that an
  844. %% indirect effect causes an automatic state transition from
  845. %% state Z1 with positive effects P1 and negative effects N1 to
  846. %% state Z2 with positive effects P2 and negative effects N2
  847. %%
  848. causes(Z,P,N,Z2) :-
  849.    causes(Z,P,N,Z1,P1,N1) -> causes(Z1,P1,N1,Z2)
  850.                            ; Z2=Z.
  851.  
  852. %%
  853. %% ramify(Z1,ThetaP,ThetaN,Z2)
  854. %%
  855. %% state Z2 is the result of applying causal relationships after
  856. %% removing the negative direct effects ThetaN and adding the
  857. %% positive direct effects ThetaP to state Z2
  858. %%
  859. ramify(Z1,ThetaP,ThetaN,Z2) :-
  860.    update(Z1,ThetaP,ThetaN,Z), causes(Z,ThetaP,ThetaN,Z2).
  861.    
  862.    
  863. %% additional predicates necessary for Sicstus
  864.  
  865. nonground(X):- \+ ground(X).
  866.  
  867. instance1(X,Y):- subsumes_chk(Y,X).
  868.  
  869.  
  870.  
  871.  
  872.  
  873.  
  874.  
  875. ?-w_dt(((_G1917=2;true),(_G1928=_G1928;true),(_G1917=2;true)))
  876. % autoloading user:autoload/0 from /usr/local/lib/swipl-7.3.16/library/prolog_autoload
  877. % autoloading prolog_codewalk:must_be/2 from /usr/local/lib/swipl-7.3.16/library/error
  878. % autoloading record:member/2 from /usr/local/lib/swipl-7.3.16/library/lists
  879. % autoloading user:maplist/2 from /usr/local/lib/swipl-7.3.16/library/apply
  880. % autoloading oset:reverse/2 from /usr/local/lib/swipl-7.3.16/library/lists
  881. % autoloading prolog_codewalk:portray_clause/1 from /usr/local/lib/swipl-7.3.16/library/listing
  882. % autoloading prolog_codewalk:clause_info/4 from /usr/local/lib/swipl-7.3.16/library/prolog_clause
  883. % autoloading prolog_codewalk:initialization_layout/4 from /usr/local/lib/swipl-7.3.16/library/prolog_clause
  884. % autoloading prolog_codewalk:gtrace/0 from /usr/local/lib/swipl-7.3.16/xpce/prolog/lib/gui_tracer
  885. % autoloading pce_principal:load_foreign_library/1 from /usr/local/lib/swipl-7.3.16/library/shlib
  886. % autoloading pce_principal:unlock_predicate/1 from /usr/local/lib/swipl-7.3.16/library/system
  887. % autoloading pce_expansion:push_operators/1 from /usr/local/lib/swipl-7.3.16/library/operators
  888. % autoloading pce_expansion:pop_operators/0 from /usr/local/lib/swipl-7.3.16/library/operators
  889. % autoloading pce_realise:last/2 from /usr/local/lib/swipl-7.3.16/library/lists
  890. % autoloading prolog_debug:backtrace/1 from /usr/local/lib/swipl-7.3.16/library/prolog_stack
  891. % autoloading error:assertion/1 from /usr/local/lib/swipl-7.3.16/library/debug
  892. % autoloading pce_host:send/2 from /usr/local/lib/swipl-7.3.16/xpce/prolog/lib/pce
  893. % autoloading pce_portray:portray_clause/1 from /usr/local/lib/swipl-7.3.16/library/listing
  894. % autoloading prolog_codewalk:clause_name/2 from /usr/local/lib/swipl-7.3.16/library/prolog_clause
  895. % Autoloader: iteration 1 resolved 28 predicates and loaded 18 files in 0.188 seconds.  Restarting ...
  896. % autoloading pce_goal_expansion:pce_error/1 from /usr/local/lib/swipl-7.3.16/xpce/prolog/lib/swi_compatibility
  897. % autoloading pce_goal_expansion:append/3 from /usr/local/lib/swipl-7.3.16/library/lists
  898. % autoloading pce_expansion:pce_error/1 from /usr/local/lib/swipl-7.3.16/xpce/prolog/lib/swi_compatibility
  899. % autoloading pce_expansion:append/3 from /usr/local/lib/swipl-7.3.16/library/lists
  900. % autoloading pce_expansion:pce_info/1 from /usr/local/lib/swipl-7.3.16/xpce/prolog/lib/swi_compatibility
  901. % autoloading pce_expansion:reverse/2 from /usr/local/lib/swipl-7.3.16/library/lists
  902. % autoloading pce_expansion:maplist/3 from /usr/local/lib/swipl-7.3.16/library/apply
  903. % autoloading pce_expansion:flatten/2 from /usr/local/lib/swipl-7.3.16/library/lists
  904. % autoloading pce_realise:pce_error/1 from /usr/local/lib/swipl-7.3.16/xpce/prolog/lib/swi_compatibility
  905. % autoloading pce_host:get/3 from /usr/local/lib/swipl-7.3.16/xpce/prolog/lib/pce
  906. % autoloading gui_tracer:debug/0 from /usr/local/lib/swipl-7.3.16/library/edinburgh
  907. % autoloading pce_global:append/3 from /usr/local/lib/swipl-7.3.16/library/lists
  908. % autoloading pce_global:gensym/2 from /usr/local/lib/swipl-7.3.16/library/gensym
  909. % autoloading quintus:date_time_value/3 from /usr/local/lib/swipl-7.3.16/library/date
  910. % autoloading pce_principal:pce_info/1 from /usr/local/lib/swipl-7.3.16/xpce/prolog/lib/swi_compatibility
  911. % autoloading pce_messages:get/3 from /usr/local/lib/swipl-7.3.16/xpce/prolog/lib/pce
  912. % Autoloader: iteration 2 resolved 3 predicates and loaded 16 files in 0.136 seconds.  Restarting ...
  913. % Autoloader: loaded 31 files in 3 iterations in 0.447 seconds
  914. % autoloading user:expects_dialect/1 from /usr/local/lib/swipl-7.3.16/library/dialect
  915. % autoloading chr:expects_dialect/1 from /usr/local/lib/swipl-7.3.16/library/dialect
  916. % autoloading chr_translate:portray_clause/1 from /usr/local/lib/swipl-7.3.16/library/listing
  917. % autoloading chr_translate:flatten/2 from /usr/local/lib/swipl-7.3.16/library/lists
  918. % autoloading chr_translate:selectchk/3 from /usr/local/lib/swipl-7.3.16/library/lists
  919. % autoloading chr_translate:nth1/3 from /usr/local/lib/swipl-7.3.16/library/lists
  920. % autoloading chr_translate:is_set/1 from /usr/local/lib/swipl-7.3.16/library/lists
  921. % autoloading chr_translate:append/2 from /usr/local/lib/swipl-7.3.16/library/lists
  922. % autoloading chr_translate:select/3 from /usr/local/lib/swipl-7.3.16/library/lists
  923. % autoloading chr_translate:nth1/4 from /usr/local/lib/swipl-7.3.16/library/lists
  924. % autoloading chr_translate:predsort/3 from /usr/local/lib/swipl-7.3.16/library/sort
  925. % autoloading chr_translate:numlist/3 from /usr/local/lib/swipl-7.3.16/library/lists
  926. % autoloading sort:must_be/2 from /usr/local/lib/swipl-7.3.16/library/error
  927. % autoloading guard_entailment:member/2 from /usr/local/lib/swipl-7.3.16/library/lists
  928. % autoloading guard_entailment:append/3 from /usr/local/lib/swipl-7.3.16/library/lists
  929. % autoloading sicstus:read_line_to_codes/2 from /usr/local/lib/swipl-7.3.16/library/readutil
  930. % autoloading chr_runtime:permission_error/3 from /usr/local/lib/swipl-7.3.16/library/error
  931. % autoloading builtins:append/3 from /usr/local/lib/swipl-7.3.16/library/lists
  932. % autoloading block_directive:permission_error/3 from /usr/local/lib/swipl-7.3.16/library/error
  933. % autoloading block_directive:instantiation_error/1 from /usr/local/lib/swipl-7.3.16/library/error
  934. % autoloading block_directive:domain_error/2 from /usr/local/lib/swipl-7.3.16/library/error
  935. % Autoloader: iteration 1 resolved 2 predicates and loaded 18 files in 0.413 seconds.  Restarting ...
  936. % Autoloader: loaded 2 files in 2 iterations in 0.807 seconds
  937. % autoloading user:make/0 from /usr/local/lib/swipl-7.3.16/library/make
  938. % autoloading user:check/0 from /usr/local/lib/swipl-7.3.16/library/check
  939. % Checking undefined predicates ...
  940. % Checking trivial failures ...
  941. % Checking redefined system and global predicates ...
  942. % autoloading check:predicate_name/2 from /usr/local/lib/swipl-7.3.16/library/prolog_clause
  943. % substitute/4                 Redefined global predicate
  944. % prolog_flag/2                Redefined global predicate
  945. % sublist/2                    Redefined global predicate
  946. % Checking predicates with declarations but without clauses ...
  947. % Checking predicates that need autoloading ...
  948. % autoloading check:clause_info/4 from /usr/local/lib/swipl-7.3.16/library/prolog_clause
  949. % autoloading check:clause_name/2 from /usr/local/lib/swipl-7.3.16/library/prolog_clause
  950. % Autoloader: loaded 0 files in 1 iterations in 0.412 seconds
  951.  
Advertisement
Add Comment
Please, Sign In to add comment
Advertisement