1:- dynamic current_state/1.    2
    3init_simulator :- init_scenario,
    4                  retract_all(current_state(_)), assert(current_state([])).
    5
    6:- dynamic wumpus/2,pit/2,gold/2.    7
    8init_scenario :-
    9
   10        retract_all(wumpus(_,_)), retract_all(pit(_,_)),retract_all(gold(_,_)), 
   11        
   12        dimension(Dim),
   13        
   14        real_world(Dim,World),
   15        
   16        ( foreach(Element,World) do
   17            ( Element = at(wumpus,cell(X,Y)) ->
   18                assert(wumpus(X,Y))
   19            ;
   20                ( Element = at(gold,cell(X,Y)) ->
   21                    assert(gold(X,Y))
   22                ;
   23                    Element = pit(cell(X,Y)),
   24                    assert(pit(X,Y)) ) ) ).
   68perform(turn, []) :-
   69	write('turn'), nl,
   70	current_state([at(X,Y),facing(D)]),
   71	retract(current_state([at(X,Y),facing(D)])),
   72	( D < 4 -> D1 is D+1 ; D1 is 1 ),
   73	assert(current_state([at(X,Y),facing(D1)])).
   74
   75perform(enter, [Breeze,Stench,Glitter]) :-
   76	write('enter'), nl,
   77	current_state(Z),
   78	retract(current_state(Z)),
   79	assert(current_state([at(1,1),facing(1)])),
   80	( gold(1,1) -> Glitter = true ; Glitter = false ),
   81	( (wumpus(1,2) ; wumpus(2,1)) -> Stench = true ;
   82	    Stench = false ),
   83	( (pit(2,1) ; pit(1,2)) -> Breeze = true ;
   84	    Breeze = false ).
   85
   86perform(exit, []) :-
   87	write('exit'), nl,
   88	current_state([at(X,Y),facing(D)]),
   89	retract(current_state([at(X,Y),facing(D)])),
   90	assert(current_state([])).
   91
   92perform(grab, []) :-
   93	write('grab'), nl.
   94
   95perform(shoot, [Scream]) :-
   96	write('shoot'), nl,
   97	current_state([at(X,Y),facing(D)]),
   98	wumpus(WX, WY),
   99	( in_direction(X, Y, D, WX, WY), Scream = true ; Scream = false ).
  100
  101perform(go, [Breeze,Stench,Glitter]) :-
  102	write('go'), nl,
  103	current_state([at(X,Y),facing(D)]),
  104	retract(current_state([at(X,Y),facing(D)])),
  105	( D = 1 -> X1 is X, Y1 is Y+1 ;
  106	  D = 3 -> X1 is X, Y1 is Y-1 ;
  107	  D = 2 -> X1 is X+1, Y1 is Y ;
  108	  D = 4 -> X1 is X-1, Y1 is Y ),
  109	assert(current_state([at(X1,Y1),facing(D)])),
  110	( gold(X1,Y1) -> Glitter = true ; Glitter = false ),
  111	X_east is X1+1, X_west is X1-1, Y_north is Y1+1, Y_south is Y1-1,
  112	( (wumpus(X_east,Y1) ; wumpus(X1,Y_north) ;
  113           wumpus(X_west,Y1) ; wumpus(X1,Y_south)) -> Stench = true ;
  114	    Stench = false ),
  115	( (pit(X_east,Y1) ; pit(X1,Y_north) ;
  116           pit(X_west,Y1) ; pit(X1,Y_south)) -> Breeze = true ;
  117	    Breeze = false ).
  118
  119
  120
  121%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  122%%                                                           %%
  123%%  The real world                                           %%
  124%%                                                           %%
  125%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  129real_world(4,[at(wumpus,cell(2,4)),
  130            pit(cell(4,2)),
  131            at(gold,cell(4,4))]).
  132
  133real_world(8,[at(wumpus,cell(6,6)),
  134            at(gold,cell(7,6)),
  135            pit(cell(7,3)),
  136            pit(cell(5,3)),
  137            pit(cell(4,3)),
  138            pit(cell(5,7)),
  139            pit(cell(3,4))]).
  140
  141real_world(16,[at(wumpus,cell(9,6)),
  142               at(gold,cell(11,13)),
  143               pit(cell(2,3)),
  144               pit(cell(2,10)),
  145               pit(cell(5,4)),
  146               pit(cell(3,5)),
  147               pit(cell(8,6)),
  148               pit(cell(9,8)),
  149               pit(cell(13,8)),
  150               pit(cell(5,10)),
  151               pit(cell(11,11)),
  152               pit(cell(7,13))]).
  153
  154real_world(32,[at(wumpus,cell(8,13)),
  155               at(gold,cell(26,30)),
  156               pit(cell(4,1)),
  157               pit(cell(10,3)),
  158               pit(cell(18,3)),
  159               pit(cell(24,4)),
  160               pit(cell(6,5)),
  161               pit(cell(12,6)),
  162               pit(cell(28,6)),
  163               pit(cell(21,7)),
  164               pit(cell(21,8)),
  165               pit(cell(16,9)),
  166               pit(cell(5,10)),
  167               pit(cell(12,12)),
  168               pit(cell(21,12)),
  169               pit(cell(26,12)),
  170               pit(cell(4,13)),
  171               pit(cell(6,13)),
  172               pit(cell(10,13)),
  173               pit(cell(13,14)),
  174               pit(cell(6,15)),
  175               pit(cell(10,15)),
  176               pit(cell(29,15)),
  177               pit(cell(19,16)),
  178               pit(cell(23,16)),
  179               pit(cell(8,19)),
  180               pit(cell(15,19)),
  181               pit(cell(21,20)),
  182               pit(cell(25,20)),
  183               pit(cell(12,21)),
  184               pit(cell(6,22)),
  185               pit(cell(15,24)),
  186               pit(cell(21,24)),
  187               pit(cell(8,25)),
  188               pit(cell(28,25)),
  189               pit(cell(30,25)),
  190               pit(cell(25,26)),
  191               pit(cell(5,27)),
  192               pit(cell(12,28)),
  193               pit(cell(23,28)),
  194               pit(cell(8,30)),
  195               pit(cell(17,30))
  196              ])