The Wumpus World in Jess

The Wumpus world problem is another Artificial Intelligence Toy Problem, which exists in many different forms and versions. Solving the Wumpus World in Jess, as stated by this instructions from the California Polytechnic State University was recently a topic in the AI class of my master studies. A Wumpus world example is shown in the figure below:

Wumpus world example

The World consists of caves organized in a grid. Every such entry in the grid can either be a cave (white) or not be a cave (grey, none contained in the image above). The human in the bottom left corner is the hunter who tries to find the gold and exit the world again, which he has entered at location 1/1 (this location is the only entrance/exit for this world). Basically the hunter can go up/down/left/right to adjacent caves (if there are such ones), observe effects that are placed on the cave he currently stands on (stench or breeze), collect the gold if it’s in the same cave — and he can leave the world again at location 1/1. The overall task is to leave the world which having collected the gold previously.

The mentioned effects breeze and stench are caused by pits and the Wumpus: each cave that is next to a pit contains a breeze and each cave that is next to the Wumpus contains a stench. If the hunter runs into a pit or the Wumpus he will die — therefore it is useful to observe breeze or stench, as they indicate danger. The world is only partially observable for the hunter: he can only observe effects that are in the same cave as the hunter — but he can remember, what he has already seen in the past and do reasoning to conclude new facts from this knowledge. Further, the world is deterministic (actions done by the hunter lead to the expected result for sure). In our version of the game the Wumpus (and of course the pits) cannot move, and the hunter can shoot an arrow either up, down, left or right to kill the Wumpus, if he is located in this direction. To not have a hunter simply shooting arrows in all directions, the number of arrows is limited to 1 (so if he fails to kill with the first shot, he has no further possibility to kill the wumpus).

Jess
Jess is a framework in Java, that can be used to build rule-based expert systems (can decide things by deriving new information from current information, similar to what humans can do). Beside the Jess library to use in Java, Jess provides an own “rule language” in which facts can be stated and rules can be defined, which later match to the facts and trigger the derivation of new facts. This is what gets used for our Wumpus world problem: the initial facts (position of hunter, Wumpus, pits, etc.) get added to our knowledge database. Then the hunter can operate on this knowledge database to derive new facts by thinking, and also to move around, observe new facts from the world, etc. (note: the hunter uses the same knowledge database that also contains facts about the whole world, but he only uses those informations that are available to him — so he does not cheat).

Implementation
I implemented the first three of the four tasks stated in the instructions (the optional part of making the Wumpus move would not have been too complicated, as it basically includes the same logic as for the hunter — but it would be a lot of work on which I currently don’t want to spend too much time).

The more interesting part was task 3: giving the hunter the ability to go to a distant cave he has already seen in the past — and making this work for all imaginable world configurations. An example of the world 3 configuration one will run into with a hunter that does not have the ability to go to a distant cave is shown below. The H corresponds to the hunter’s position, D to his goal at a distant cave, G to the gold, W to the dead Wumpus (shot by the hunter before), P to pits, E to the entrance/exit and gray fields to “no-caves”. The hunter has already seen the cave at 6/5 to which he wants to go to, but currently stands in the cave at 1/4.

Go to a distant cave

One of the approaches to guide the hunter to such distant caves is algorithmically actually pretty simple: check if the hunter is somewhere on the way from the distant cave back to the entrance. If he is, he is already on the “right way”, and goes one step towards the distant cave. If he is not, he currently is not on the “right way”, and therefore goes one step back towards the entrance. This approach works in all cases, as the hunter creates a spanning tree of caves as he enters new caves. If he already is in the correct branch of the tree, he can continue to go down to the target cave. If he is not, he has to go up towards the root cave (entrance) — which is part of the correct way in all cases, as all caves the hunter can see must be reachable from there. Implementing this procedure in Jess is a bit tricky from syntax point of view (requires functions and queries), but is still pretty straight.

Download
The download contains the world rules (ww.jess, how the hunter thinks and acts, code attached below for quick review), the world setups for cave 0-3, and the file to start the program easily (start.clp).
Jess Source Code, sha1: 396cb4ecd2f54c9f05b1d4daa0fc9ae6d053103f.

; AI Homework Project: JESS and the Wumpus world
;
; Rainhard Findling
; Department of Mobile Computing
; University of Applied Sciences Upper Austria
; 2012-05-27
;
;; global variables -----------------------------------------------------------

(defglobal ; these global variables encode the strength of desires
?*veryhigh* = 5
?*high* = 4
?*medium* =  3
?*low* = 2
?*verylow* = 1 )

;; templates -----------------------------------------------------------------

(deftemplate hunter "A hunter"
(slot agent (default Xena))
(slot x (type INTEGER))
(slot y (type INTEGER))
(slot gold (default 0)(type INTEGER))
(slot alive (default TRUE))
(slot arrows (type INTEGER)(default 1))
(slot killed-wumpi (type INTEGER)(default 0))
)

(deftemplate desire "a hunter's desires"
(slot agent)
(slot strength (type INTEGER))
(slot action)
(slot x)
(slot y))

(deftemplate goal "a hunter's goals"
(slot agent)
(slot action)
(slot x)
(slot y))

(deftemplate cave
"Cave objects sore the hunter's model of the world"
(slot x (type INTEGER))		; (x,y) coordinates of cave
(slot y (type INTEGER))		;
(slot fromx (default -1))		; coordinates of the cave from which we
(slot fromy (default -1))		;   first entered the cave.
(slot seenfromx (default -1))		; coordinates of the cave from which we
(slot seenfromy (default -1))		;   first saw the cave.
(slot visited (default FALSE))	; Has the hunter been in it?
(slot stench (default UNKNOWN))	; Does the cave smell?
(slot breeze (default UNKNOWN))	; Is it breezy?
(slot glitter (default UNKNOWN))	; Is there a glitter in it?
(slot has-wumpus (default UNKNOWN))	; Is there a wumpus here?
(slot has-pit (default UNKNOWN))	; Is there a pit here?
(slot has-gold (default UNKNOWN))	; Is their gold here?
(slot safe (default UNKNOWN))	; Is the cave safe -- no wumpus, no pit?
)

(deftemplate nocave
"a nocave assertion is used to indicate a cell in the world that is
not a cave.  (nocave (x 3)(y 3)) means that (3,3) is not a cave."
(slot x (type INTEGER))
(slot y (type INTEGER)))

(deftemplate wumpus "a wumpus"
(slot x (type INTEGER))
(slot y (type INTEGER))
(slot alive (default TRUE)))

(deftemplate pit "A pit"
(slot x (type INTEGER))
(slot y (type INTEGER)))

(deftemplate gold "Gold has a location and amount."
(slot x (type INTEGER))
(slot y (type INTEGER))
(slot amount (type INTEGER)(default 10)))

(deftemplate exit "coordinates of the entrance/exit to the caves."
(slot x)
(slot y))

;; functions -----------------------------------------------------------------

(deffunction buildworld (?width ?height)
;; (buildworld N M) makes cave assertions for a NxM rectangular  world.
(printout t "Adding adj asserts for a " ?width " by " ?height "  world." crlf)
(bind ?x 1)
(while (        (bind ?y 1)
(while ( ?x 1) then (assert (adj ?x ?y (- ?x 1) ?y)))
(if (> ?y 1) then (assert (adj ?x ?y ?x (- ?y 1))))
(if (< ?x ?width) then (assert (adj ?x ?y (+ ?x 1) ?y)))
(if (< ?y ?height) then (assert (adj ?x ?y ?x (+ ?y 1))))             (bind ?y (+ 1 ?y)))         (bind ?x (+ ?x 1)))) (defquery query-access-cave     "returns iterator of caves at x,y"     (declare (variables ?x ?y))     (cave (x ?x)(y ?y)(fromx ?fromx)(fromy ?fromy)) ) (deffunction next-step-on-way-to-goal (?hunter ?x1 ?y1 ?exit)     "call with the 'predecessor' of the distant cave the hunter wants to go to"     ;search for intersection     (bind ?continue TRUE)     (while ?continue	         ;check next field (if hunter is on this field, done below) 	    ;remark: x,y is one step closer to the goal then it's predecessor fromx, fromy 		(bind ?result (run-query* query-access-cave ?x1 ?y1))    	    (?result next)         (bind ?fromx (integer (?result getString fromx)))             (bind ?fromy (integer (?result getString fromy)))           ;check if we are already at the entrance 		(if (and (eq ?x1 (fact-slot-value ?exit x))(eq ?y1 (fact-slot-value ?exit y))) then 			;we are already at the entrance, so the hunter 			;is not on the correct path currently 			;move him towards the entrance by moving him to the cave he came ftom             (bind ?result (run-query* query-access-cave (fact-slot-value ?hunter x) (fact-slot-value ?hunter y)))     		    (?result next) 	        (bind ?fromx (integer (?result getString fromx)))     	        (bind ?fromy (integer (?result getString fromy)))   			(printout t "#hunter is not on path from goal to exit, moving him to (" ?fromx "," ?fromy ")" crlf)     		(modify ?hunter (x ?fromx)(y ?fromy))             (bind ?continue FALSE) 		else 	        ;check if hunter is at the x,y position 			(if (and (eq ?fromx (fact-slot-value ?hunter x)) (eq ?fromy (fact-slot-value ?hunter y))) then 	        	(printout t "#hunter is on correct way to goal, moving him to (" ?x1 "," ?y1 ")" crlf) 		    	;hunter is on correct path, move him to x,y 		        ;--> one step closer to goal now
(modify ?hunter (x ?x1)(y ?y1))
(bind ?continue FALSE)
else
;check next field
(bind ?x1 ?fromx)
(bind ?y1 ?fromy)
)
)
)
)

;; rules --------------------------------------------------------------------

(defrule in-the-beginning
(initial-fact)
=>
(printout t "GENESIS..." crlf)
(assert (task genesis)))

;; GENESIS rules  --------------------------------------------------------------

(defrule buildworld
"This rule will call the buildworld function which will add the adj/4
assertions for the current world"
(task genesis)
(worldsize ?width ?height)
=>
(buildworld ?width ?height))

(defrule retract-nocaves
"This rule will retract adj/4 assertions added by buildworld when a
matching nocave assertion is present"
(task genesis)
(nocave (x ?x)(y ?y))
?adj
(retract ?adj))

(defrule put-hunter-in-caves
"Assuming the hunter has no (X,Y) in the caves, find an exit
and put him there."
(task genesis)
?hunter
(printout t ?a " enters the caves at (" ?x "," ?y ")." crlf)
(modify ?hunter (x ?x)(y ?y)))

;; SIMULATE rules --------------------------------------------------------------

(defrule meet-the-wumpus
"If a hunter and wumpus are in the same cave..."
(task simulate)
?hunter
(printout t "Aaarrrggghhhhhh....munch...munch...munch" crlf)
(modify ?hunter (alive FALSE))
(halt))

(defrule fall-into-the-pit
"If a hunter and pit are in the same cave..."
(task simulate)
?hunter
(printout t "Aaarrrggghhhhhh....plop" crlf)
(modify ?hunter (alive FALSE))
(halt))

;; SENSE rules --------------------------------------------------------------

(defrule enter-new-cave
"If we are in a cave for the first time, mark it as visited.
This rule is only needed when the hunter wakes up in the exit cave"
(task sense)
(hunter (agent ?agent) (x ?x) (y ?y))
(not (cave (x ?x)(y ?y)))
=>
;(printout t ?agent " enters (" ?x "," ?y ")." crlf)
(assert (cave (x ?x)(y ?y)(visited TRUE))))

(defrule enter-cave-for-first-time
"If we are in a cave for the first time, mark it as visited"
(task sense)
(hunter (agent ?agent) (x ?x) (y ?y))
?cave
;(printout t ?agent " enters (" ?x "," ?y ")." crlf)
(modify ?cave (visited TRUE)))

(defrule notice-other-caves
"If we've just entered a new cave, we notice the other adjacent caves."
(task sense)
(hunter (agent ?agent) (x ?x)(y ?y))
(adj ?x ?y ?x2 ?y2)
(not (cave (x ?x2)(y ?y2)))
=>
(printout t ?agent " notices (" ?x2 "," ?y2 ") nearby." crlf)
(assert (cave (x ?x2)(y ?y2)(seenfromx ?x)(seenfromy ?y)))
)

(defrule sense-breeze
"Sense a breeze if a pit is nearby"
(task sense)
(hunter (agent ?agent) (x ?x) (y ?y))
?cave
(printout t ?agent " feels a breeze in (" ?x "," ?y ")." crlf)
(modify ?cave (breeze TRUE)))

(defrule sense-breeze-none
"Sense a breeze if a pit is nearby"
(declare  (salience -1))
(task sense)
(hunter (agent ?agent) (x ?x) (y ?y))
?cave
(printout t ?agent " feels no breeze in (" ?x "," ?y ")." crlf)
(modify ?cave (breeze FALSE)))

(defrule sense-stench
"Sense a stench if a living wumpus is nearby"
(task sense)
(hunter (agent ?agent) (x ?x) (y ?y))
?cave
(printout t ?agent " smells a stench." crlf)
(modify ?cave (stench TRUE)))

(defrule sense-stench-none
"Sense a stench if a living wumpus is nearby"
(declare (salience -1))
(task sense)
(hunter  (agent ?agent)(x ?x) (y ?y))
?cave
(printout t  ?agent " smells nothing." crlf)
(modify ?cave (stench FALSE)))

(defrule sense-glitter
"Sense glitter if gold in this cave"
(task sense)
(hunter  (agent ?agent) (x ?x) (y ?y))
?cave  ?n 0))
=>
(printout t   ?agent " sees glitter." crlf)
(modify ?cave (glitter TRUE)))

(defrule sense-glitter-none
"Sense a breeze if gold in this cave"
(task sense)
(hunter (agent ?a)(x ?x) (y ?y))
?cave  ?n 0))))
=>
(printout t ?a " sees no glitter." crlf)
(modify ?cave (glitter FALSE))
)

;; THINK rules --------------------------------------------------------------

(defrule evaluate-stench-none
(task think)
(cave (x ?x)(y ?y)(stench FALSE))
(adj ?x ?y ?x2 ?y2)
?f
(printout t "No stench in (" ?x "," ?y ") means no wumpus in (" ?x2 ","  ?y2 ")." crlf)
(modify ?f (has-wumpus FALSE)))

(defquery query-neighbors-that-possibly-or-for-sure-hold-wumpus
"returns an iterator of neighboring caves of cave x,y that possibly or for sure hold a wumpus"
(declare (variables ?a ?b))
(adj ?a ?b ?a2 ?b2)
(cave (x ?a2)(y ?b2)(has-wumpus ~FALSE))
)

(defrule evaluate-stench
(task think)
?cave     (adj ?x ?y ?x2 ?y2)
?f
;check amount of neighbors of x,y that can hold a wumpus
;it it's one only, he has the wumpus for sure
;can also be done when agent is not on x,y, therefore use UNKOWN or MAYBE
(bind ?count (count-query-results query-neighbors-that-possibly-or-for-sure-hold-wumpus ?x ?y))
(if (= 1 ?count) then
(printout t "#With stench in (" ?x "," ?y "), the wumpus is in (" ?x2  "," ?y2 ") for sure." crlf)
(modify ?f (has-wumpus TRUE)(safe FALSE))
else
;only mark field as "maybe wumpus" if it is wumpus status is currently unknown
(if (= UNKNOWN (fact-slot-value ?f has-wumpus)) then
(printout t "#With stench in (" ?x "," ?y "), maybe the wumpus is in (" ?x2  "," ?y2 ")." crlf)
(modify ?f (has-wumpus MAYBE))
)
)
)

(defrule evaluate-breeze-none
(task think)
(cave (x ?x)(y ?y)(breeze FALSE))
(adj ?x ?y ?x2 ?y2)
?f
(printout t "There's no breeze in (" ?x "," ?y ") so there's no pit  in (" ?x2  "," ?y2 ")." crlf)
(modify ?f (has-pit FALSE))
)

(defquery query-neighbors-that-possibly-or-for-sure-hold-pit
"returns an iterator of neighboring caves of cave x,y that possibly or for sure hold a pit"
(declare (variables ?a ?b))
(adj ?a ?b ?a2 ?b2)
(cave (x ?a2)(y ?b2)(has-pit ~FALSE))
)

(defrule evaluate-breeze
(task think)
(cave (x ?x)(y ?y)(breeze TRUE))
?cave
;check amount of neighbors of x,y that can hold a pit
;it it's one only, he has the pit for sure
;can also be done when agent is not on x,y, therefore use UNKOWN or MAYBE
(bind ?count (count-query-results query-neighbors-that-possibly-or-for-sure-hold-pit ?x ?y))
(if (= 1 ?count) then
(printout t "#With breeze in (" ?x "," ?y "), the pit is in (" ?x2  "," ?y2 ") for sure." crlf)
(modify ?cave (has-pit TRUE)(safe FALSE))
else
;only mark field as "maybe pit" if its pit status is currently unknown
(if (= UNKNOWN (fact-slot-value ?cave has-pit)) then
(printout t "#With breeze in (" ?x "," ?y "), maybe the pit is in (" ?x2  "," ?y2 ")." crlf)
(modify ?cave (has-pit MAYBE))
)
)
)

(defrule evaluate-glitter
(task think)
(hunter (agent ?a)(x ?x)(y ?y))
?cave
(printout t "Seeing glitter, " ?a " knows there is gold in (" ?x "," ?y ")." crlf)
(modify ?cave (has-gold TRUE)))

(defrule evaluate-glitter-none
(task think)
(hunter (agent ?a)(x ?x)(y ?y))
?cave
(printout t "Seeing no glitter, " ?a " knows there is no gold in (" ?x "," ?y ")." crlf)
(modify ?cave (has-gold FALSE)))

(defrule safe-cave
(task think)
(or ?f
(printout t "With neither wumpus nor pit, (" ?x "," ?y ") is safe." crlf)
(modify ?f (safe TRUE)))

(defrule safe-cave2
(task think)
(hunter (agent ?agent) (x ?x)(y ?y)(alive TRUE))
?f
(printout t "Since " ?agent " is in ("?x "," ?y ") and not dead, it must be safe." crlf)
(modify ?f (safe TRUE))
)

(defrule safe-cave3
"safe => ~wumpus ^ ~pit"
(task think)
(or ?f         ?f
(printout t "(" ?x "," ?y ") is safe, so there's no pit or wumpus in it." crlf)
(modify ?f (has-pit FALSE))
(bind ?w (fact-slot-value ?f has-wumpus))
(if (= ?w DEAD) then
;this field contains a dead wumpus, do not mark it as wumpus-free
else
;no dead wumpus + we alive = no wumpus here
(modify ?f (has-wumpus FALSE))
)
)

;; setting desires ...

(defrule desire-to-leave-caves
(task think)
;check that we have gold and killed a wumpus
(hunter (agent ?a)(x ?x)(y ?y)(gold ~0)(killed-wumpi ~0))
;(cave (x ?x)(y ?y)(has-exit TRUE))
(exit (x ?x)(y ?y))
=>
(printout t "Having found the gold, " ?a " want to leave the caves." crlf)
(assert (desire (agent ?a)(strength ?*veryhigh*)(action leavecaves))))

(defrule add-desire-to-head-for-the-exit
(task think)
(hunter (agent ?agent) (x ?x)(y ?y)(gold ~0)(killed-wumpi ~0))
(cave (x ?x)(y ?y)(fromx ?fx)(fromy ?fy))
(test (> ?fx 0))
=>
(printout t ?agent " strongly wants to go to (" ?fx "," ?fy ") to leave the cave." crlf)
(assert (desire (agent ?agent) (strength ?*veryhigh*) (action go)(x ?fx)(y ?fy))))

(defrule lust-for-gold
(task think)
(hunter (agent ?a)(x ?x)(y ?y))
(cave (x ?x)(y ?y)(has-gold TRUE))
=>
(printout t ?a " wants to pick up the gold in (" ?x "," ?y ")." crlf)
(assert (desire (agent ?a)(strength ?*veryhigh*)(action pickupgold))))

(defrule lust-for-shoot
"if the hunter is next to a field that is known to contain a wumpus, he wants to kill the wumpus"
(task think)
(cave (x ?x)(y ?y)(has-wumpus TRUE))
(hunter (agent ?a)(x ?x2)(y ?y2))
(adj ?x ?y ?x2 ?y2)
=>
(printout t "#" ?a " wants to shoot the wumpus in (" ?x "," ?y ")." crlf)
(assert (desire (agent ?a)(strength ?*veryhigh*)(action shoot))))

(defrule retract-lesser-desire
"If we have two desires for the same thing, remove the one with lesser strength"
(task think)
(desire (agent ?agent)(strength ?s1)(action ?a)(x ?x)(y ?y))
?desire2     (test (< ?s2 ?s1))     =>
(retract ?desire2))

(defrule add-desire-to-go-to-safe-adjacent-cave
"go to an adjacent, safe, unvisited cave"
(task think)
(hunter (agent ?agent)(x ?x)(y ?y))
(adj ?x ?y ?x2 ?y2)
(cave (x ?x2)(y ?y2)(visited FALSE)(safe TRUE))
=>
(printout t ?agent " strongly wants to go to (" ?x2 "," ?y2 ")." crlf)
(assert (desire (agent ?agent) (strength ?*high*) (action go)(x ?x2)(y ?y2))))

(defrule add-desire-to-go-to-safe-distant-cave
"go to a non-adjacent, safe, unvisited cave"
(task think)
(hunter (agent ?agent)(x ?x)(y ?y))
(cave (x ?x2)(y ?y2)(visited FALSE)(safe TRUE))
(not (adj ?x ?y ?x2 ?y2))
=>
(printout t ?agent " moderately wants to go to (" ?x2 "," ?y2 ")." crlf)
(assert (desire (agent ?agent) (strength ?*medium*) (action go)(x ?x2)(y ?y2))))

(defrule add-desire-to-go-to-risky-adjacent-cave
"go to an adjacent, risky, unvisited cave"
(task think)
(hunter (agent ?agent)(x ?x)(y ?y))
(cave (x ?x2)(y ?y2)(visited FALSE)(safe UNKNOWN))
(adj ?x ?y ?x2 ?y2)
=>
(printout t ?agent " somewhat wants to go to (" ?x2 "," ?y2 ")." crlf)
(assert (desire (agent ?agent) (strength ?*low*) (action go)(x ?x2)(y  ?y2))))

(defrule add-desire-to-go-to-risky-distant-cave
"go to a distant, risky, unvisited cave"
(task think)
(hunter (agent ?agent)(x ?x)(y ?y))
(cave (x ?x2)(y ?y2)(visited FALSE)(safe UNKNOWN))
(not (adj ?x ?y ?x2 ?y2))
=>
(printout t ?agent " somewhat wants to go to (" ?x2 "," ?y2 ")." crlf)
(assert (desire (agent ?agent) (strength ?*verylow*) (action go)(x ?x2)(y  ?y2))))

;; PLAN rules  --------------------------------------------------------------

;; Planning our action is just simply picking the desire to realize
;; and asserting an appropriate goal.

(defrule choose-desire
"pick the best desire available for a given action. note that we
will only promote one desire to be a goal at a time."
(task plan)
?f  ?s2 ?s))))
(not (goal))
=>
(retract ?f)
(assert (goal (action ?act) (x ?x)(y ?y))))

;; ACT rules  --------------------------------------------------------------

;; These rules find a goal and take actions to carry it out.

(defrule found-exit
"If the hunter has gold and finds an exit, she leaves."
(task act)
?goal
(printout t ?agent " leaves the caves." crlf)
(halt))

(defrule pickup-gold
"If we find the gold, pick it up"
(task act)
?goal     ?f1     ?cave     ?f2  ?more 0))
=>
(printout t ?a " picks up " ?more " pieces of gold!" crlf)
(retract ?goal)
(modify ?f1 (gold (+ ?current ?more)))
(modify ?cave (has-gold FALSE)(glitter FALSE))
(modify ?f2 (amount 0)))

(defrule go-to-adjacent-cave
"If our desire is to goto XY and were are in an adjacent cell,
do it and remove the desire"
(task act)
?goal     ?hunter     (adj ?x ?y ?x2 ?y2)
?target
(printout t ?agent " goes to (" ?x "," ?y ")." crlf)
(retract ?goal)
(modify ?hunter (x ?x)(y ?y))
(if (not ?v) then (modify ?target (fromx ?x2)(fromy ?y2))))

(defrule shoot
"if there is a cave x,y with an wumpus on it an a adjacent cave x2,y2 with the hunter on it, the hunter kills the wumpus"
(task act)
?goal     ;wumpus for later modification
;pos and state unknown - that's why we don't access it's x,y or alive state
?wumpus     ;cave witch is known to have a wumpus
?cave     ;hunter pos x2,y2 and hunter alive
?hunter
;remember arrow amount
(bind ?arrows (fact-slot-value ?hunter arrows))
;get wumpus
(if (> ?arrows 0) then
;we have arrows, kill wumpus, reduce arrows by one, set wumpus to false
(retract ?goal)
(printout t "#Hunter at (" ?x2 "," ?y2 ") kills wumpus at (" ?x "," ?y ")." crlf)
(modify ?wumpus (alive FALSE))
(bind ?killed-wumpi (fact-slot-value ?hunter killed-wumpi))
(modify ?hunter (killed-wumpi (+ ?killed-wumpi 1)))
(modify ?hunter (arrows (- ?arrows 1)))
(modify ?cave (has-wumpus DEAD))
else
;damn, no arrows ._.
(printout t "#Hunter at (" ?x2 "," ?y2 ") would like to kill wumpus at (" ?x "," ?y "), but has no arrows." crlf)
)
)

(defrule move-toward-distant-cave
"The hunter is in X1Y1 and intends to go to distant X3Y3.  Hunter
goes to adjacent safe cave X2Y2 which is closer to X3Y3."
(task act)
(goal (action go) (x ?x3)(y ?y3))
;idea: go back to entrance, hope that the distant cave is adjacent to a cave on our way.
?hunter     ;?cave     ?goalcave     (not (adj ?x1 ?y1 ?x3 ?y3))
?exit
;(printout t "#goal (" ?x3 "," ?y3 ") seenfrom (" ?seenfromx "," ?seenfromy ")." crlf)
(next-step-on-way-to-goal ?hunter ?seenfromx ?seenfromy ?exit)
)

(defrule delete-desires
"retracts any desire facts in the database"
(task act)
(deletedesires)
?f
(retract ?f))

(defrule delete-desires-end
"retracts any desire facts in the database"
(task act)
(deletedesires)
(not (desire))
=>
(retract (deletedesires)))

(defrule retract-satisfied-goal
;; this shouldn't happen, and is here for debugging.
(task act)
?goal
(printout t "WARNING: " ?a " has a goal to go to (" ?x "," ?y ")
and she is already here." crlf)
(retract ?goal))

(defrule retract-satisfied-goal
;; this shouldn't happen, and is here for debugging.
(declare (salience -1))
(task act)
?goal
(printout t "WARNING: unsatisfied goal: " ?act " " ?x " " ?y "."  crlf)
(halt))

;; TASK SWITCHING rules -------------------------------------------------------

;; These rules cycle us through the various tasks.  Note that they all
;; have a very low salience, so that they will be run last.  Depending
;; on which is the current task, the rules just move us on to the
;; next.  we start in genesis, the move to a cycle of (simulate,
;; sense, think, plan, act).

(defrule genesis-to-simulate
(declare  (salience -100))
?f
(retract ?f)
(printout t "SIMULATING..." crlf)
(assert (task simulate)))

(defrule simulate-to-sense
(declare  (salience -100))
?f
(retract ?f)
(printout t "SENSING..." crlf)
(assert (task sense)))

(defrule sense-to-think
(declare  (salience -100))
?f
(retract ?f)
(printout t "THINKING..." crlf)
(assert (task think)))

(defrule think-to-plan
(declare  (salience -100))
?f
(retract ?f)
(printout t "PLANNING..." crlf)
(assert (task plan)))

(defrule plan-to-act
(declare  (salience -100))
?f
(retract ?f)
(printout t "ACTING..." crlf)
(assert (task act)))

(defrule act-to-simulate
(declare  (salience -100))
?f
(retract ?f)
(printout t "SIMULATING..." crlf)
(assert (task simulate)))

One thought on “The Wumpus World in Jess

  1. I think I read somewhere that topologically speaking the grid used in the Wumpus game is actually a graph whose vertices are rooms and whose edges are the tunnels between rooms, wrapping around the surface of a sphere. Just a fascinating tidbit I picked up along the way.
    I wrote my own ANSI version of Wumpus once, but it was a grid with random squares designated as rock and depicted using Unicode block characters. Never finished writing the game though.

Leave a comment