2:- dynamic gridsize/1.    3gridsize(8).
    4
    5elementary_action(enter).
    6elementary_action(exit).
    7elementary_action(turn).
    8elementary_action(grab).
    9elementary_action(shoot).
   10elementary_action(go).
   11compound_action(go_to(_,_)).
   12
   13 :-dynamic(state_update/4).   14
   15 state_update(Z1,enter,Z2,[B,S,G]) :-
   16   update(Z1,[at(1,1),facing(2)],[],Z2),
   17   breeze_perception(1,1,B,Z2),
   18   stench_perception(1,1,S,Z2),
   19   glitter_perception(1,1,G,Z2).
   20
   21 state_update(Z1,exit,Z2,[]) :-
   22   holds(facing(D),Z1),
   23   update(Z1,[],[at(1,1),facing(D)],Z2).
   24
   25   /*
   26 state_update(Z1,turn,Z2,[]) :-
   27   holds(facing(D),Z1),
   28   (D#<4 #/\ D1#=D+1) #\/ (D#=4 #/\ D1#=1),
   29   update(Z1,[facing(D1)],[facing(D)],Z2).
   30*/
   31
   32state_update(A57, turn, A59, []) :-
   33        holds(facing(A69), A57),
   34        /*fd_arith : */ fd_gec_ent(0, -1, A69, 3, 0, A85),
   35        /*fd_arith : */ fd_eq([-1, -1 * A69, 1 * B06], A94),
   36        /*fd_arith : */ fd_eq([-2, 1 * A85, 1 * A94], B15),
   37        '#='(A69, 4, B34),
   38        '#='(B06, 1, B41),
   39        /*fd_arith : */ fd_eq([-2, 1 * B34, 1 * B41], B50),
   40        /*fd_arith : */ fd_gec(B15, 1, B50, -1, 0),
   41        update(A57, [facing(B06)], [facing(A69)], A59).
   42
   43
   44 state_update(Z1,grab,Z2,[]) :-
   45   holds(at(X,Y),Z1),
   46   update(Z1,[has(gold)],[gold(X,Y)],Z2).
   47
   48 state_update(Z1,shoot,Z2,[S]) :-
   49   ( S=true, update(Z1,[dead],[has(arrow)],Z2)
   50     ; S=false, update(Z1,[],[has(arrow)],Z2) ).
   51
   52 state_update(Z1,go,Z2,[B,S,G]) :-
   53   holds(at(X,Y),Z1), holds(facing(D),Z1),
   54   adjacent(X,Y,D,X1,Y1),
   55   update(Z1,[at(X1,Y1)],[at(X,Y)],Z2),
   56   breeze_perception(X1,Y1,B,Z2),
   57   stench_perception(X1,Y1,S,Z2),
   58   glitter_perception(X1,Y1,G,Z2).
   59
   60 state_update(Z1,go_to(X1,Y1),Z2,[]) :-
   61   holds(at(X,Y),Z1),
   62   update(Z1,[at(X1,Y1)],[at(X,Y)],Z2).
   63
   64    :-dynamic(stench_perception/4).   65
   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([wumpus(XE,Y),wumpus(X,YN),
   75              wumpus(XW,Y),wumpus(X,YS)],Z) ).
   76*/
   77    stench_perception(X,Y,Percept,Z) :-
   78      '#='(XE,X+1),'#='(XW,X-1),'#='(YN,Y+1),'#='(YS,Y-1), 
   79      ( Percept=false, not_holds(wumpus(XE,Y),Z),
   80                       not_holds(wumpus(XW,Y),Z),
   81                       not_holds(wumpus(X,YN),Z),
   82                       not_holds(wumpus(X,YS),Z) ;
   83        Percept=true,
   84          or([wumpus(XE,Y),wumpus(X,YN),
   85              wumpus(XW,Y),wumpus(X,YS)],Z) ).
   86
   87
   88 breeze_perception(X,Y,Percept,Z) :-
   90   '#='(XE,X+1),'#='(XW,X-1),'#='(YN,Y+1),'#='(YS,Y-1), 
   91   ( Percept=false, not_holds(pit(XE,Y),Z),
   92                    not_holds(pit(XW,Y),Z),
   93                    not_holds(pit(X,YN),Z),
   94                    not_holds(pit(X,YS),Z) ;
   95     Percept=true,
   96       or([pit(XE,Y),pit(X,YN),
   97           pit(XW,Y),pit(X,YS)],Z) )
   97.
   98
   99 glitter_perception(X,Y,Percept,Z) :-
  100   Percept=false, not_holds(gold(X,Y),Z) ;
  101   Percept=true,  holds(gold(X,Y),Z).
  102
  103
  104 :-dynamic(adjacent/5).  105
  106 /*
  107 adjacent(X,Y,D,X1,Y1) :-
  108   gridsize(N),
  109   [X,Y,X1,Y1]::1..N, D::1..4,
  110       (D#=1) #/\ (X1#=X)   #/\ (Y1#=Y+1) % north
  111   #\/ (D#=3) #/\ (X1#=X)   #/\ (Y1#=Y-1) % south
  112   #\/ (D#=2) #/\ (X1#=X+1) #/\ (Y1#=Y)   % east
  113   #\/ (D#=4) #/\ (X1#=X-1) #/\ (Y1#=Y).  % west
  114 */
  115
  116adjacent(A57, A58, A59, A60, A61) :-
  117        gridsize(A66),
  118    '::'([A57, A58, A60, A61], '..'(1 , A66)),
  119    fd_domain : fd_dom_simple(A59, dom(['..'(1,4)], 4)),
  120        #=(A59, 1, B07),
  121        #=(A60, A57, B14),
  122        /*fd_arith : */ fd_eq([-2, 1 * B07, 1 * B14], B23),
  123        /*fd_arith : */ fd_eq([-1, -1 * A58, 1 * A61], B44),
  124        /*fd_arith : */ fd_eq([-2, 1 * B23, 1 * B44], B65),
  125        #=(A59, 3, B84),
  126        #=(A60, A57, B91),
  127        /*fd_arith : */ fd_eq([-2, 1 * B84, 1 * B91], C00),
  128        /*fd_arith : */ fd_eq([1, -1 * A58, 1 * A61], C21),
  129        /*fd_arith : */ fd_eq([-2, 1 * C00, 1 * C21], C42),
  130        /*fd_arith : */ fd_gec_ent(B65, 1, C42, -1, 0, C67),
  131        #=(A59, 2, C74),
  132        /*fd_arith : */ fd_eq([-1, -1 * A57, 1 * A60], C83),
  133        /*fd_arith : */ fd_eq([-2, 1 * C74, 1 * C83], D04),
  134        #=(A61, A58, D23),
  135        /*fd_arith : */ fd_eq([-2, 1 * D04, 1 * D23], D32),
  136        /*fd_arith : */ fd_gec_ent(C67, 1, D32, -1, 0, D57),
  137        #=(A59, 4, D64),
  138        /*fd_arith : */ fd_eq([1, -1 * A57, 1 * A60], D73),
  139        /*fd_arith : */ fd_eq([-2, 1 * D64, 1 * D73], D94),
  140        #=(A61, A58, E13),
  141        /*fd_arith : */ fd_eq([-2, 1 * D94, 1 * E13], E22),
  142        /*fd_arith : */ fd_gec(D57, 1, E22, -1, 0).
  143
  144
  145init(Z0) :- Z0 = [has(arrow),wumpus(WX,WY)|Z],
  146	    gridsize(N),
  147            '::'([WX,WY] , ['..'(1,N)]),
  148            not_holds(wumpus(1,1),Z0),
  149            not_holds_all(wumpus(_,_),Z),
  150            not_holds(dead,Z),
  151            not_holds(pit(1,1),Z),
  152            N2 is N+1,
  153            not_holds_all(pit(_,0),Z), %boundary
  154            not_holds_all(pit(_,N2),Z),
  155            not_holds_all(pit(0,_),Z),
  156            not_holds_all(pit(N2,_),Z),
  157            not_holds_all(at(_,_),Z),
  158            not_holds_all(facing(_),Z),
  159            duplicate_free(Z0).
  160
  161
  162 main_wumpus :- init(Z0), execute(enter,Z0,Z1),
  163         Cpts=[1,1,[1,2]], Vis=[[1,1]], Btr=[], 
  164         main_loop(Cpts,Vis,Btr,Z1).
  165
  166
  167 main_loop([X,Y,Choices|Cpts],Vis,Btr,Z) :-
  168   Choices=[Dir|Dirs] ->
  169     (explore(X,Y,Dir,Vis,Z,Z1) ->
  170        knows_val([X1,Y1],at(X1,Y1),Z1),
  171        hunt_wumpus(X1,Y1,Z1,Z2),
  172        (knows(gold(X1,Y1),Z2) ->
  173           execute(grab,Z2,Z3), go_home(Z3)
  174         ; Cpts1=[X1,Y1,[1,2,3,4],X,Y,Dirs|Cpts],
  175           Vis1=[[X1,Y1]|Vis], Btr1=[X,Y|Btr],
  176           main_loop(Cpts1,Vis1,Btr1,Z2) )
  177      ; main_loop([X,Y,Dirs|Cpts],Vis,Btr,Z) )
  178   ; backtrack(Cpts,Vis,Btr,Z).
  179
  180 explore(X,Y,D,V,Z1,Z2) :-
  181   adjacent(X,Y,D,X1,Y1), \+ member([X1,Y1],V),
  182   knows_not(pit(X1,Y1),Z1),
  183   (knows_not(wumpus(X1,Y1),Z1);knows(dead,Z1)),
  184   turn_to(D,Z1,Z), execute(go,Z,Z2).
  185
  186 backtrack(_,_,[],Z) :- execute(exit,Z,_).
  187 backtrack(Cpts,Vis,[X,Y|Btr],Z) :- 
  188   go_back(X,Y,Z,Z1), main_loop(Cpts,Vis,Btr,Z1).
  189
  190 go_back(X,Y,Z1,Z2) :-
  191   holds(at(X1,Y1),Z1), adjacent(X1,Y1,D,X,Y),
  192   turn_to(D,Z1,Z), execute(go,Z,Z2).
  193 turn_to(D,Z1,Z2) :-
  194   knows(facing(D),Z1) -> Z2=Z1
  195   ; execute(turn,Z1,Z), turn_to(D,Z,Z2).
  196
  197 hunt_wumpus(X,Y,Z1,Z2) :-
  198   \+ knows(dead,Z1),
  199   knows_val([WX,WY],wumpus(WX,WY),Z1),
  200   in_direction(X,Y,D,WX,WY)
  201   -> turn_to(D,Z1,Z), execute(shoot,Z,Z2)
  202    ; Z2=Z1.
  203
  204:-dynamic(in_direction/5).  205/*
  206 in_direction(X,Y,D,X1,Y1) :-
  207   gridsize(N),
  208   '::'([X,Y,X1,Y1], '..'(1,N)), '::'(D,'..'(1,4)),
  209       ( D #= 1 ) #/\ (X1#=X) #/\ (Y1#>Y)  % north
  210   #\/ (D#=3) #/\ (X1#=X) #/\ (Y1#<Y)  % south
  211   #\/ (D#=2) #/\ (X1#>X) #/\ (Y1#=Y)  % east
  212   #\/ (D#=4) #/\ (X1#<X) #/\ (Y1#=Y). % west
  213*/
  214in_direction(VAR157, VAR158, VAR159, VAR160, VAR161) :-
  215        gridsize(VAR166),
  216        '::'([VAR157, VAR158, VAR160, VAR161], '..'(1 , VAR166)),
  217        fd_domain : fd_dom_simple(VAR159, dom(['..'(1,4)], 4)),
  218        #=(VAR159, 1, VAR207),
  219        #=(VAR160, VAR157, VAR214),
  220        /*fd_arith : */ fd_eq([-2, 1 * VAR207, 1 * VAR214], VAR223),
  221        /*fd_arith : */ fd_gec_ent(VAR161, -1, VAR158, -1, 0, VAR248),
  222        /*fd_arith : */ fd_eq([-2, 1 * VAR223, 1 * VAR248], VAR257),
  223        #=(VAR159, 3, VAR276),
  224        #=(VAR160, VAR157, VAR283),
  225        /*fd_arith : */ fd_eq([-2, 1 * VAR276, 1 * VAR283], VAR292),
  226        /*fd_arith : */ fd_gec_ent(VAR158, -1, VAR161, -1, 0, VAR317),
  227        /*fd_arith : */ fd_eq([-2, 1 * VAR292, 1 * VAR317], VAR326),
  228        /*fd_arith : */ fd_gec_ent(VAR257, 1, VAR326, -1, 0, VAR351),
  229        #=(VAR159, 2, VAR358),
  230        /*fd_arith : */ fd_gec_ent(VAR160, -1, VAR157, -1, 0, VAR371),
  231        /*fd_arith : */ fd_eq([-2, 1 * VAR358, 1 * VAR371], VAR380),
  232        #=(VAR161, VAR158, VAR399),
  233        /*fd_arith : */ fd_eq([-2, 1 * VAR380, 1 * VAR399], VAR408),
  234        /*fd_arith : */ fd_gec_ent(VAR351, 1, VAR408, -1, 0, VAR433),
  235        #=(VAR159, 4, VAR440),
  236        /*fd_arith : */ fd_gec_ent(VAR157, -1, VAR160, -1, 0, VAR453),
  237        /*fd_arith : */ fd_eq([-2, 1 * VAR440, 1 * VAR453], VAR462),
  238        #=(VAR161, VAR158, VAR481),
  239        /*fd_arith : */ fd_eq([-2, 1 * VAR462, 1 * VAR481], VAR490),
  240        /*fd_arith : */ fd_gec(VAR433, 1, VAR490, -1, 0).
  241
  242
  243 go_home(Z) :-
  244   plan(find_path([]),Plan,Z),
  245   distances(L), retract(distances(L)), assert(distances([])),
  246   execute(Plan,Z,Z1), execute(exit,Z1,_).
  247
  248:-dynamic(plan_proc/2).  249
  250/*
  251plan_proc(find_path(_160), _158) :-
  252        _158 = (?(home)#[?(poss_go(_174, _175, _160, _177)), go_to(_174, _175), find_path(_177)]).
  253*/
  254
  255 plan_proc(find_path(Vis),P) :-
  256   P = '#'(?(home) ,
  257        [?(poss_go(X,Y,Vis,Vis1)), go_to(X,Y),
  258	 find_path(Vis1)]).
  259
  260 home(S,Z) :- knows(at(1,1),S,Z).
  261
  262:- dynamic(distances/1).  263:- assert(distances([])).  264
  265poss_go(X1,Y1,Vis,Vis1,S,Z) :-
  266   knows_val([X,Y],at(X,Y),S,Z),
  267   ( D=1 ; D=2 ; D=3 ; D=4 ),
  268   adjacent(X,Y,D,X1,Y1),
  269   \+ member([X1,Y1],Vis),
  270   knows_not(pit(X1,Y1),Z),
  271   ( \+ knows(dead,Z)->knows_not(wumpus(X1,Y1),Z)
  272     ; true ),
  273   Vis1=[[X,Y]|Vis],
  274   distances(L), length(Vis1,N), \+ ( member([X1,Y1,M],L), M=<N ),
  275   retract(distances(L)), assert(distances([[X1,Y1,N]|L])).
  276
  277plan_cost(find_path(_), Plan, Cost) :-
  278   length(Plan, Cost).
  279
  280 execute_compound_action(go_to(X,Y),Z1,Z2) :-
  281   holds(at(X1,Y1),Z1), adjacent(X1,Y1,D,X,Y),
  282   turn_to(D,Z1,Z), execute(go,Z,Z2)