Code

(defconstant player-tokens '(x o x o x o x o x))
(defconstant move-numbers  '(1 2 3 4 5 6 7 8 9))
(defconstant all-runs '((0 1 2)
                        (3 4 5)
                        (6 7 8)
                        (0 3 6)
                        (1 4 7)
                        (2 5 8)
                        (0 4 8)
                        (2 4 6)))

(defclass player ()
  ((name :accessor player-name :initarg :name :initform 'emanon)))

(defclass random-machine-player (player) ())
(defclass human-player (player) ())
(defclass heuristic-machine-player (player)
  ((rules :accessor heuristic-machine-player-rules
          :initform NIL)))

(defmethod make-rule ((l list))
  `(if   (prefix of ,l matches the play so far)
       then (select move from ,l)))

(defmethod add-rule ((p heuristic-machine-player) (l list))
  (setf (heuristic-machine-player-rules p)
        (append (heuristic-machine-player-rules p)
                (list (make-rule l))))
  nil)

(defmethod add-rules ((p heuristic-machine-player) (n integer))
  (dotimes (i n)
    (add-rule p (winning-play)))
  nil)

(defmethod winning-play ()
  (let ((p (play)))
    (if (eq (game-over-p p) 'w)
      p
      (winning-play))))

(defmethod display ((p random-machine-player))
  (format t "RANDOM MACHINE PLAYER ...~%")
  (format t "name = ~A~%" (player-name p))
  (terpri)
  nil)

(defmethod display ((p human-player))
  (format t "HUMAN PLAYER ...~%")
  (format t "name = ~A~%" (player-name p))
  (terpri)
  nil)

(defmethod display ((p heuristic-machine-player))
  (format t "HEURISTIC MACHINE PLAYER ...~%")
  (format t "name = ~A~%" (player-name p))
  (format t "number of rules = ~A~%" (length
                                      (heuristic-machine-player-rules p)))
  (format t "rules ...~%")
  (dolist (rule (heuristic-machine-player-rules p))
    (print-rule rule)
    (terpri))
  (terpri)
  nil)

(defmethod print-rule ((rule list))
  (format t "~A ~A~%~A ~A~%"
          (first rule) (second rule) (third rule) (fourth rule))
  nil)

(defmethod make-move ((p random-machine-player) (report t))
  (let ((move (select *avail*)))
    (when report
      (format t "BEGIN RANDOM PLAYER MOVE ...~%")
      (format t "randomly selecting ~A for my move ~%" move)
      (format t "END RANDOM PLAYER MOVE ...~%"))
    (setf *avail* (remove move *avail*))
    move))

(defmethod make-move ((p human-player) (report t))
  (when report
    (format t "BEGIN HUMAN PLAYER MOVE ...~%"))
  (format t "Please select a move from ~A~%" *avail*)
  (let ((move (read)))
    (if (not (member move *avail*))
      (make-move p)
      (setf *avail* (remove move *avail*)))
    (when report
      (format t "END HUMAN PLAYER MOVE~%"))
    move))

(defmethod make-move ((p heuristic-machine-player) (report t))
  (when report
    (format t "BEGIN HEURISTIC PLAYER MOVE ...~%"))
  (let ((rule (select-from-rule-base p)))
    (if (null rule)
      (progn
        (setf move (select *avail*))
        (setf *nr-random-moves-by-hmp* (1+ *nr-random-moves-by-hmp*))
        (setf *most-recent-hmp-move* 'random)
        (when report
          (format t "making random move ~A since no rule is applicable.~%"
                  move)))
      (progn
        (setf move (apply-rule rule))
        (setf *nr-heuristic-moves-by-hmp* (1+ *nr-heuristic-moves-by-hmp*))
        (setf *most-recent-hmp-move* 'heuristic)
        (when report
          (format t "play so far = ~A~%" *play-so-far*)
          (format t "Making move ~A by applying the rule ...~%" move)
          (print-rule rule))))
    (setf *avail* (remove move *avail*))
    (when report
      (format t "END HEURISTIC PLAYER MOVE~%"))
    move))

(defmethod select-from-rule-base ((p heuristic-machine-player))
  (let ((rule-base (heuristic-machine-player-rules p)))
    (first (remove-if-not #'applicablep rule-base))))

(defmethod applicablep ((rule list))
  (setf the-play (third (second rule)))
  (matches *play-so-far* the-play))

(defmethod matches ((psf list) (play list))
  (cond
   ((null psf) t)
   ((eq (car psf) (car play))
    (matches (cdr psf)
             (cdr play)))))

(defmethod apply-rule ((rule list))
  (let ((the-play (fourth (fourth rule))))
    (nth (length *play-so-far*)
         the-play)))

(defmethod generic-play ((x player) (o player) (report t) &aux move)
  (setf *avail*       '(nw n ne w c e sw s se))
  (setf *play-so-far* ())
  (dolist (player '(x o x o x o x o x))
    (when (or report (equal (type-of o) 'human-player-machine))
      (visualize *play-so-far*))
    (cond
     ((eq player 'x) (setf move (make-move x report)))
     ((eq player 'o) (setf move (make-move o report))))
    (setf *play-so-far* (snoc move *play-so-far*))
    (when (game-over-p *play-so-far*)
      (return nil)))
  *play-so-far*)

(defmethod generic-play-with-stats ((x player) (o player) (report t))
  (setf *avail* '(nw n ne w c e sw s se))
  (setf *play-so-far* ())
  (let (move)
    (dolist (player '(x o x o x o x o x))
      (visualize *play-so-far*)
      (cond
       ((eq player 'x)
        (setf move (make-move x report)))
       ((eq player 'o)
        (setf move (make-move o report))))
      (setf *play-so-far* (snoc move *play-so-far*))
      (when (game-over-p *play-so-far*)
        (return nil)))
    (cond
     ((eq (game-over-p *play-so-far*) 'w)
      (cond
       ((eq *most-recent-hmp-move* 'random)
        (setf *nr-random-move-wins-by-hmp*
              (1+ *nr-random-move-wins-by-hmp*)))
       ((eq *most-recent-hmp-move* 'heuristic)
        (setf *nr-heuristic-move-wins-by-hmp*
              (1+ *nr-heuristic-move-wins-by-hmp*)))))))
  *play-so-far*)

(defmethod game-over-p ((play list))
  (cond
   ((line-p (odd play))  'w)
   ((line-p (even play)) 'l)
   ((= (length play) 9)  'd)))

(defmethod odd ((l list))
  (cond
   ((null l) ())
   ((null (cdr l)) (list (car l)))
   (t (cons (car l)
            (odd (cddr l))))))

(defmethod even ((l list))
  (cond
   ((null l) ())
   ((null (cdr l)) ())
   (t (cons (cadr l)
            (even (cddr l))))))

(defun line (&rest line)
  (or (subsetp '(nw n ne) line)
      (subsetp '( w c  e) line)
      (subsetp '(sw s se) line)
      (subsetp '(nw w sw) line)
      (subsetp '(n  c s ) line)
      (subsetp '(ne e se) line)
      (subsetp '(nw c se) line)
      (subsetp '(ne c sw) line)))

(defmethod line-p ((l list))
  (cond
   ((< (length l) 3)
    nil)

   ((= (length l) 3)
    (line (first  l)
          (second l)
          (third  l)))

   ((= (length l) 4)
    (or
     (line (first l)  (second l) (third l))
     (line (first l)  (second l) (fourth l))
     (line (first l)  (third l)  (fourth l))
     (line (second l) (third l)  (fourth l))))

   ((= (length l) 5)
    (or
     (line (first l)  (second l) (third l))
     (line (first l)  (second l) (fourth l))
     (line (first l)  (second l) (fifth l))
     (line (first l)  (third l)  (fourth l))
     (line (first l)  (third l)  (fifth l))
     (line (second l) (third l)  (fourth l))
     (line (second l) (third l) (fifth l))
     (line (second l) (fourth l) (fifth l))
     (line (third l) (fourth l) (fifth l))))))

(defmethod demo-random-random ()
  (let* ((x (make-instance 'random-machine-player))
         (o (make-instance 'random-machine-player))
         (p (generic-play x o t)))
    (format t "~A~%" p)
    (visualize p)
    (format t "~A~%" (game-over-p p))
    nil))

(defmethod demo-random-human ()
  (let* ((x (make-instance 'random-machine-player))
         (o (make-instance 'human-player))
         (p (generic-play x o t)))
    (format t "~A~%" p)
    (visualize p)
    (format t "~A~%" (game-over-p p))
    nil))

(defmethod demo-human-random ()
  (let* ((x (make-instance 'human-player))
         (o (make-instance 'random-machine-player))
         (p (generic-play x o t)))
    (format t "~A~%" p)
    (visualize p)
    (format t "~A~%" (game-over-p p))
    nil))


(defmethod multi-nth ((ns list) (the-list list))
  (mapcar (lambda (n) (nth n the-list))
          ns))

(defmethod get-all-runs ((play list))
  (mapcar (lambda (ns) (multi-nth ns play))
          all-runs))

(defmethod take ((n integer) (the-list list))
  (if (or (= n 0)
          (null the-list))
    nil
    (cons (car the-list)
          (take (1- n)
                (cdr the-list)))))

(defmethod sort-by-nth ((list-of-lists list) (n integer) (predicate function))
  (sort list-of-lists
        (lambda (x y) (funcall predicate (nth n x) (nth n y)))))

(defmethod select ((the-list list))
  (let ((n (random (length the-list))))
    (nth n the-list)))

(defmethod snoc (element (the-list list))
  (append the-list
          (list element)))

(defmethod play ()
  (let* ((play  ())
         (avail '(nw n ne w c e sw s se)))
    (dolist (player player-tokens)
      (cond
       ((eq player 'x)
        (setf move (select avail))
        (setf avail (remove move avail))
        (setf play (snoc move play)))

       ((eq player 'o)
        (setf move (select avail))
        (setf avail (remove move avail))
        (setf play (snoc move play)))))
    play))

(defmethod print-row ((row list))
  (format t "~{~{~A~D~}~^║~}~%" row))

(defmethod print-row-sep ()
  (format t "══╬══╬══~%"))

(defmethod outcome-move ((tokens-moves list))
  (let ((tokens (mapcar #'first  tokens-moves))
        (moves  (mapcar #'second tokens-moves)))
    (list (apply   #'max moves)
          (outcome tokens))))

(defmethod outcome ((tokens list))
  (cond
   ((equal tokens '(x x x)) 'w)
   ((equal tokens '(o o o)) 'l)
   (T                       nil)))

(defmethod sort-by-position ((play list))
  (let ((location-token-move (mapcar #'list play
                                            player-tokens
                                            move-numbers)))
    (mapcar #'cdr
            (mapcar (lambda (location)
                      (assoc location location-token-move))
                    '(nw n ne
                       w c  e
                      sw s se)))))

(defmethod sort-by-position* ((play list))
  (let ((location-token-move (mapcar #'list play
                                            player-tokens
                                            move-numbers)))
    (mapcar #'cdr
            (mapcar (lambda (location)
                      (or (assoc location location-token-move)
                          (list location " " " ")))
                    '(nw n ne
                       w c  e
                      sw s se)))))

(defmethod visualize ((play list))
  (let ((positions (sort-by-position* play)))
    (print-row (subseq positions 0 3))
    (print-row-sep)
    (print-row (subseq positions 3 6))
    (print-row-sep)
    (print-row (subseq positions 6 9)))
  nil)

(defmethod analyze ((play list))
  (let* ((positions      (sort-by-position play))
         (tokens-moves   (get-all-runs positions))
         (outcomes-moves (mapcar #'outcome-move tokens-moves))
         (winning-moves  (remove-if (lambda (x) (null (second x)))
                                    outcomes-moves)))
    (if winning-moves
      (second (first (sort-by-nth winning-moves 0 #'<)))
      'D)))

(defmethod demo-va ()
  (let ((p (play)))
    (format t "~A~%" p)
    (visualize p)
    (format t "~A~%" (analyze p)))
  nil)

(defmethod stats ((n integer) (demo t))
  (when demo
    (format t "BEGIN GATHERING STATISTICS ...~%"))
  (let ((w 0)
        (l 0)
        (d 0))
    (dotimes (i n)
      (let* ((p (play))
             (result (analyze p)))
        (when demo
          (format t "~A~%" p)
          (visualize p)
          (format t "~A~%" result))
        (cond
         ((eq result 'w) (setf w (1+ w)))
         ((eq result 'l) (setf l (1+ l)))
         ((eq result 'd) (setf d (1+ d))))))
    (let ((results (mapcar #'probability
                           (list w l d)
                           (list n n n))))
      (when demo
        (format t "END GATHERING STATISTICS~%"))
      (mapcar #'list
              '(w l d)
              results))))

(defmethod probability ((special integer) (total integer))
  (float (/ special
            total)))


(defmethod demo-heuristic-human ((nr-rules integer) &aux p x o)
  (setf *nr-random-moves-by-hmp* 0)
  (setf *nr-heuristic-moves-by-hmp* 0)
  (setf *nr-random-move-wins-by-hmp* 0)
  (setf *nr-heuristic-move-wins-by-hmp* 0)

  (setf x (make-instance 'heuristic-machine-player :name 'hm))
  (add-rules x nr-rules)
  (display x)

  (setf o (make-instance 'human-player :name 'hu))
  (display o)

  (setf p (generic-play-with-stats x o t))

  (format t "GAME SUMMARY~%")
  (format t "Play of the game = ~A~%" p)
  (visualize p)

  (format t "~A~%" (game-over-p p))
  (format t "HEURISTIC USE SUMMARY~%")
  (summarize-heuristic-use)

  nil)

(defmethod summarize-heuristic-use ()
  (format t "random move count = ~A and heuristic move count = ~A~%"
          *nr-random-moves-by-hmp* *nr-heuristic-moves-by-hmp*)
  (format t "random move wins = ~A and heuristic move wins = ~A~%"
          *nr-random-move-wins-by-hmp* *nr-heuristic-move-wins-by-hmp*)
  nil)

(defmethod demo-heuristic-random ((nr-rules integer) &aux p x o)
  (setf *nr-random-moves-by-hmp* 0)
  (setf *nr-heuristic-moves-by-hmp* 0)
  (setf *nr-random-move-wins-by-hmp* 0)
  (setf *nr-heuristic-move-wins-by-hmp* 0)

  (setf x (make-instance 'heuristic-machine-player :name 'hm))
  (add-rules x nr-rules)
  (display x)

  (setf o (make-instance 'random-machine-player :name 'rm))
  (display o)

  (setf p (generic-play-with-stats x o t))

  (format t "GAME SUMMARY~%")
  (format t "Play of the game = ~A~%" p)
  (visualize p)

  (format t "~A~%" (game-over-p p))
  (format t "HEURISTIC USE SUMMARY~%")
  (summarize-heuristic-use)

  nil)

Demo

[1]> (load "ttt4.l")
;; Loading file ttt4.l ...
;; Loaded file ttt4.l
T
[2]> (demo-heuristic-human 25)
HEURISTIC MACHINE PLAYER ...
name = HM
number of rules = 25
rules ...
IF (PREFIX OF (SW W C NW NE SE N E S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SW W C NW NE SE N E S))

IF (PREFIX OF (NW SE SW W NE S E N C) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NW SE SW W NE S E N C))

IF (PREFIX OF (S W SE E N C NW SW NE) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (S W SE E N C NW SW NE))

IF (PREFIX OF (E NE W SW N SE NW S C) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (E NE W SW N SE NW S C))

IF (PREFIX OF (SE W NE S C SW E N NW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SE W NE S C SW E N NW))

IF (PREFIX OF (S NW N SE C W SW NE E) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (S NW N SE C W SW NE E))

IF (PREFIX OF (NW NE C S N W SE SW E) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NW NE C S N W SE SW E))

IF (PREFIX OF (SW N E C W NE S SE NW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SW N E C W NE S SE NW))

IF (PREFIX OF (SE NW NE N C E W S SW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SE NW NE N C E W S SW))

IF (PREFIX OF (E SE C NE S NW N W SW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (E SE C NE S NW N W SW))

IF (PREFIX OF (C NE SW S W SE E NW N) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (C NE SW S W SE E NW N))

IF (PREFIX OF (NE SW N W NW E SE S C) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NE SW N W NW E SE S C))

IF (PREFIX OF (W E SE NE NW SW C N S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (W E SE NE NW SW C N S))

IF (PREFIX OF (SW W C N NE S E SE NW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SW W C N NE S E SE NW))

IF (PREFIX OF (SW C S W NE E SE N NW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SW C S W NE E SE N NW))

IF (PREFIX OF (C SW S NE E N W SE NW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (C SW S NE E N W SE NW))

IF (PREFIX OF (NW NE SE S W E C N SW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NW NE SE S W E C N SW))

IF (PREFIX OF (C SE NW S W N SW NE E) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (C SE NW S W N SW NE E))

IF (PREFIX OF (NW E SW NE S N C W SE) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NW E SW NE S N C W SE))

IF (PREFIX OF (SW NE N W S NW C E SE) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SW NE N W S NW C E SE))

IF (PREFIX OF (NE NW E C N W SE SW S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NE NW E C N W SE SW S))

IF (PREFIX OF (NW S W N NE SE E SW C) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NW S W N NE SE E SW C))

IF (PREFIX OF (S C SE W NE NW E N SW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (S C SE W NE NW E N SW))

IF (PREFIX OF (E S C SE W NE NW N SW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (E S C SE W NE NW N SW))

IF (PREFIX OF (NE NW W SW SE N E S C) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NE NW W SW SE N E S C))


HUMAN PLAYER ...
name = HU

      
══╬══╬══
      
══╬══╬══
      
BEGIN HEURISTIC PLAYER MOVE ...
play so far = NIL
Making move SW by applying the rule ...
IF (PREFIX OF (SW W C NW NE SE N E S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SW W C NW NE SE N E S))
END HEURISTIC PLAYER MOVE
      
══╬══╬══
      
══╬══╬══
X1    
BEGIN HUMAN PLAYER MOVE ...
Please select a move from (NW N NE W C E S SE)
c
END HUMAN PLAYER MOVE
      
══╬══╬══
  O2  
══╬══╬══
X1    
BEGIN HEURISTIC PLAYER MOVE ...
play so far = (SW C)
Making move S by applying the rule ...
IF (PREFIX OF (SW C S W NE E SE N NW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SW C S W NE E SE N NW))
END HEURISTIC PLAYER MOVE
      
══╬══╬══
  O2  
══╬══╬══
X1X3  
BEGIN HUMAN PLAYER MOVE ...
Please select a move from (NW N NE W E SE)
se
END HUMAN PLAYER MOVE
      
══╬══╬══
  O2  
══╬══╬══
X1X3O4
BEGIN HEURISTIC PLAYER MOVE ...
making random move E since no rule is applicable.
END HEURISTIC PLAYER MOVE
      
══╬══╬══
  O2X5
══╬══╬══
X1X3O4
BEGIN HUMAN PLAYER MOVE ...
Please select a move from (NW N NE W)
nw
END HUMAN PLAYER MOVE
GAME SUMMARY
Play of the game = (SW C S SE E NW)
O6    
══╬══╬══
  O2X5
══╬══╬══
X1X3O4
L
HEURISTIC USE SUMMARY
random move count = 1 and heuristic move count = 2
random move wins = 0 and heuristic move wins = 0
NIL
[3]> (demo-heuristic-human 25)
HEURISTIC MACHINE PLAYER ...
name = HM
number of rules = 25
rules ...
IF (PREFIX OF (C NE NW SE SW N W E S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (C NE NW SE SW N W E S))

IF (PREFIX OF (E S NW NE SE SW C W N) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (E S NW NE SE SW C W N))

IF (PREFIX OF (E S W N C NW NE SE SW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (E S W N C NW NE SE SW))

IF (PREFIX OF (W SE SW N C NE NW E S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (W SE SW N C NE NW E S))

IF (PREFIX OF (S W NW SW SE NE C N E) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (S W NW SW SE NE C N E))

IF (PREFIX OF (N C NE S SE SW NW W E) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (N C NE S SE SW NW W E))

IF (PREFIX OF (N W C E S SW NW SE NE) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (N W C E S SW NW SE NE))

IF (PREFIX OF (NW SW W S N SE C E NE) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NW SW W S N SE C E NE))

IF (PREFIX OF (SE SW E S W C NE NW N) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SE SW E S W C NE NW N))

IF (PREFIX OF (NE SW E N C NW S W SE) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NE SW E N C NW S W SE))

IF (PREFIX OF (E SE NE W NW SW S C N) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (E SE NE W NW SW S C N))

IF (PREFIX OF (SE NE SW NW S E N W C) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SE NE SW NW S E N W C))

IF (PREFIX OF (E W N SE C NE S SW NW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (E W N SE C NE S SW NW))

IF (PREFIX OF (NE SW NW E S W SE N C) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NE SW NW E S W SE N C))

IF (PREFIX OF (SW E SE N C NE NW W S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SW E SE N C NE NW W S))

IF (PREFIX OF (NW NE W S SW N E SE C) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NW NE W S SW N E SE C))

IF (PREFIX OF (SE W NE SW E N NW S C) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SE W NE SW E N NW S C))

IF (PREFIX OF (SW C S E N SE NW W NE) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SW C S E N SE NW W NE))

IF (PREFIX OF (S SW C W E NW N NE SE) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (S SW C W E NW N NE SE))

IF (PREFIX OF (E W NE NW C S SW SE N) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (E W NE NW C S SW SE N))

IF (PREFIX OF (SE N NW C E W NE S SW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (SE N NW C E W NE S SW))

IF (PREFIX OF (C SW W NW E N S SE NE) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (C SW W NW E N S SE NE))

IF (PREFIX OF (NE SW N NW W SE C E S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NE SW N NW W SE C E S))

IF (PREFIX OF (NE C NW E N W SE SW S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (NE C NW E N W SE SW S))

IF (PREFIX OF (W E C NE S N SE SW NW) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (W E C NE S N SE SW NW))


HUMAN PLAYER ...
name = HU

      
══╬══╬══
      
══╬══╬══
      
BEGIN HEURISTIC PLAYER MOVE ...
play so far = NIL
Making move C by applying the rule ...
IF (PREFIX OF (C NE NW SE SW N W E S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (C NE NW SE SW N W E S))
END HEURISTIC PLAYER MOVE
      
══╬══╬══
  X1  
══╬══╬══
      
BEGIN HUMAN PLAYER MOVE ...
Please select a move from (NW N NE W E SW S SE)
ne
END HUMAN PLAYER MOVE
    O2
══╬══╬══
  X1  
══╬══╬══
      
BEGIN HEURISTIC PLAYER MOVE ...
play so far = (C NE)
Making move NW by applying the rule ...
IF (PREFIX OF (C NE NW SE SW N W E S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (C NE NW SE SW N W E S))
END HEURISTIC PLAYER MOVE
X3  O2
══╬══╬══
  X1  
══╬══╬══
      
BEGIN HUMAN PLAYER MOVE ...
Please select a move from (N W E SW S SE)
se
END HUMAN PLAYER MOVE
X3  O2
══╬══╬══
  X1  
══╬══╬══
    O4
BEGIN HEURISTIC PLAYER MOVE ...
play so far = (C NE NW SE)
Making move SW by applying the rule ...
IF (PREFIX OF (C NE NW SE SW N W E S) MATCHES THE PLAY SO FAR)
THEN (SELECT MOVE FROM (C NE NW SE SW N W E S))
END HEURISTIC PLAYER MOVE
X3  O2
══╬══╬══
  X1  
══╬══╬══
X5  O4
BEGIN HUMAN PLAYER MOVE ...
Please select a move from (N W E S)
w
END HUMAN PLAYER MOVE
X3  O2
══╬══╬══
O6X1  
══╬══╬══
X5  O4
BEGIN HEURISTIC PLAYER MOVE ...
making random move S since no rule is applicable.
END HEURISTIC PLAYER MOVE
X3  O2
══╬══╬══
O6X1  
══╬══╬══
X5X7O4
BEGIN HUMAN PLAYER MOVE ...
Please select a move from (N E)
e
END HUMAN PLAYER MOVE
GAME SUMMARY
Play of the game = (C NE NW SE SW W S E)
X3  O2
══╬══╬══
O6X1O8
══╬══╬══
X5X7O4
L
HEURISTIC USE SUMMARY
random move count = 1 and heuristic move count = 3
random move wins = 0 and heuristic move wins = 0
NIL
[4]> (bye)
Bye.