From: Gilbert Baumann
Subject: Re: How to do this in Lisp?
Date: 
Message-ID: <GILBERT.96Oct12124103@ma2s2.mathematik.uni-karlsruhe.de>
In article <··········@tools.bbnplanet.com> ······@tools.bbnplanet.com (Barry Margolin) writes:
   In article <·················@netcom.com>,
   Bill Newman <·······@netcom.com> wrote:
   [...]
   >This seems like a reasonably natural and concise solution to the
   >problem.  However, I can't see how to express it elegantly in Common
   >Lisp.  All the ways that I can think of require references to members
   >of structures, so it would be impossible to implement the undo stack.

   You're right, Lisp doesn't provide a convenient way to do what you can do
   with C++ references to members.

   What you can do is pass around closures that access and update the
   structure slot:

   (defun search (thing getter updater)
     (let ((saved (funcall getter thing)))
       (funcall updater thing (do-something ...))
       ...
       (funcall updater thing saved)))

   Then a call to search when the current object is the i'th element of an
   array might look something like:

     (search array #'(lambda (a) (aref a i))
		   #'(lambda (a v) (setf (aref a i) v)))

This reminds me of some quick and dirty (dirty spot marked with XXX)
hack I done sometime ago, which mimics the behaviour of the C '&'
operator. The semantics are the same as found on the Symbolics Lisp
Machine. However they had choosen probably a more low level and
effient implementation. I want to share this hack, because it is a
convenient way to do such things as above. It basically works the same
way (passing closures around), but offers a more abstract interface.

(defstruct (locative (:print-function print-locative)
		     (:predicate locativep))  ;To be compatible with SCL
  setter getter desc)

(defun print-locative (x sink depth)
  (declare (ignore depth))
  (format sink "#<~S ~S>" 'locative (locative-desc x)))

(defmacro locf (place)
  (let ((g (gensym)))
    (cond ((listp place)
	   (let* ((gs (mapcar #'(lambda (x) (list (gensym) x)) (cdr place)))
		  (n-place `(,(car place) ,@(mapcar #'car gs))))    ;XXX
	     `(let ,gs
		(make-locative :setter #'(lambda (,g) (setf ,n-place ,g))
			       :getter #'(lambda () ,n-place)
			       :desc   ',n-place)) ))
	  (t
	   `(make-locative :setter #'(lambda (,g) (setf ,place ,g))
			   :getter #'(lambda () ,place)
			   :desc   ',place))) ))

(defun (setf location-contents) (v x)
  (funcall (locative-setter x) v))

(defun location-contents (x)
  (funcall (locative-getter x)))

[At the XXX spot it breaks on passing macro invocations as place and
introduces also superfluous binds. It also breaks on symbol macros.]

Let show what it does:

(LOCF place) returns a new locative. 'place' should be a SETFable
place. Example:

> (setq x '(a b c))
(A B C)
> (setq l (locf (cadr x)))
#<LOCATIVE (CADR #:G846)>

Now you could refer to the value of 'place' [here (cadr x)], by using
LOCATION-CONTENTS:

> (location-contents l)
B

LOCATION-CONTENTS is itself SETFable, so lets try it:

> (setf (location-contents l) 'quux)
QUUX
> x
(A QUUX C)

The place passed in LOCF is not to be understood as '(cadr x)', but as
a pointer to the car-cell of what (cdr x) gave at the point LOCF was
evaluated [Much like the '&' operator in C], so when we do:

> (push 'fred x)
(FRED A QUUX C)
> (locative-contents l)
;still is
QUUX
;even ..
> (setf (location-contents l) 'frob)
FROB
; .. does:
> x
(FRED A FROB C)

Now the search function would become:

(defun search (loc)
  (let ((saved (location-contents loc)))
    (setf (location-contents loc) (do-something ...))
    ...
    (setf (location-contents loc) saved) ))

The call would become:

(search (locf (aref array i)))

With the BINDF, posted by me on some sibling of this thread, search
would be even more dense:

(defun search (loc)
  (bindf (((location-contents loc) (do-something ...)))
     ...))

Sometimes it is worth looking, what the Symbolics had, we do not have
to reinvent everything. [This too much true for the GUI]

Having this in mind,
               Gilbert.

From: Andrew G Bachmann
Subject: Re: How to do this in Lisp?
Date: 
Message-ID: <53p716$5g8@news.acns.nwu.edu>
In article <·····················@ma2s2.mathematik.uni-karlsruhe.de>,
Gilbert Baumann <·······@ma2s2.mathematik.uni-karlsruhe.de> wrote:
>This reminds me of some quick and dirty (dirty spot marked with XXX)
>hack I done sometime ago, which mimics the behaviour of the C '&'
>operator. The semantics are the same as found on the Symbolics Lisp
>Machine. However they had choosen probably a more low level and
>effient implementation. I want to share this hack, because it is a
>convenient way to do such things as above. It basically works the same
>way (passing closures around), but offers a more abstract interface.

[code/example snipped]
>The place passed in LOCF is not to be understood as '(cadr x)', but as
>a pointer to the car-cell of what (cdr x) gave at the point LOCF was
>evaluated [Much like the '&' operator in C], so when we do:

This isn't quite true.  It doesn't keep a pointer to the car-cell of
what (cdr x) gave at the point LOCF was evaluated.  What it does keep
is the accessor function ("cadr"), and the value of the structure
being accessed.  For example:

> (setq list '(1 2 3 4 5))
(1 2 3 4 5)
> (setq loc (locf (caddr list)))
#<LOCATIVE (CADDR #:G150)>
> (location-contents loc)
3
> (push 4 (cdr list))
(4 2 3 4 5)
> list
(1 4 2 3 4 5)
> (location-contents loc)
2

Since the push destructively modified the list along the path that the
accessor function traverses, it changed where "loc" was referring to
to someplace different that the original cell.

Andy

Andrew Bachmann - Northwestern University - Institute for Learning Sciences
<a href="http://bishop.ils.nwu.edu/andy/">My Home Page</a>
From: Bill Newman
Subject: Re: How to do this in Lisp?
Date: 
Message-ID: <wnewmanDz687t.HyM@netcom.com>
In an earlier article, I wrote about the problem of automatically
undoing changes in a Go-playing program implemented in Lisp.  In
particular, I wrote

> In attempting to express this in Lisp, the problem appears in the
> implementation of Memory.  Basically, C++ allows me to create an
> object which stores a reference to an object, and a copy of its
> previous state, so that I can ask it to restore the object whenever I
> choose.  (In my program, the restoration request is issued by
> destroying the Memory object.)  I can't figure out how to create such
> a reference in Lisp.  It may be that this can't be done, at least when
> the object is a component of another object: I think I remember 
> someone slamming C/C++ for allowing references to components within
> objects in one of the Garbage Collection Wars earlier this year.

> When I use the code above, if I write e.g.
>   class Square_Of_The_Board {
>     Remembered<Color> v_current_color;
>     Remembered<Square_Of_The_Board*> v_next_in_chain;
>   };
> then whatever changes I make to the v_current_color and v_next_in_chain
> fields can automatically be undone by calling Unmake_Move.  Unmake_Move
> walks the linked list descending from Eph::s_list_head calling the
> dtor for each element, and the changes are undone.

> I received e-mail suggesting -- if I understood correctly -- that I
> can't overload assignment in Lisp, but the same effect could be
> achieved by defining my own (REVERSIBLE-ASSIGN VAR VALUE) function or
> macro in Lisp.  I can't figure out how to do even this.  Also, even if I
> could, I'd still prefer to have the reversible-ness associated with
> each variable, rather than with each assignment to each variable.  (I
> used to do it the other way around in C before I switched to C++, and
> it was a major maintenance hassle tracking down things which
> accidentally changed something irreversibly.)

Since then I have received many thoughtful e-mailed and posted
replies.  Some of them pointed me to closures (which don't
come so naturally to my C/assembly/Fortran-trained mind..) and I think
I have the solution to this problem now:

  (defvar *undo-list* nil)

  (defmacro reversible-assign (variableish-expr new-value)
    `(let ((old-value ,variableish-expr))
       (push #'(lambda () (setf ,variableish-expr old-value)) *undo-list*)
       (setf ,variableish-expr ,new-value)))

  (defun undo ()
    (if *undo-list*
        (progn (funcall (car *undo-list*))
               (pop *undo-list*))))

This was initially inspired by my misunderstanding of someone's
e-mailed suggestion, and it also seems to be what Barry Margolin
<······@tools.bbnplanet.com> suggested:

%   You're right, Lisp doesn't provide a convenient way to do what you can do
%   with C++ references to members.

%   What you can do is pass around closures that access and update the
%   structure slot:

Since the closures contain references to the parent objects as well as
the individual fields which are to be restored, this gets around the
obstacle that I remembered from the Garbage Collection Wars.

I also wrote

> Also, even if I
> could, I'd still prefer to have the reversible-ness associated with
> each variable, rather than with each assignment to each variable.  (I 
> used to do it the other way around in C before I switched to C++, and
> it was a major maintenance hassle tracking down things which
> accidentally changed something irreversibly.)

to which Seth Tisue <·······@nwu.edu> replied

+ Hmm... I would have imagined that there would be only one place in
+ your code where you change the board -- the function where you
+ calculate the effect of a player placing a piece on the board.  

As Lee Schumacher <····@redbrick.com> replied to a slightly different
question,

$ Usually, yes.  My guess is that he's saving and undoing more than
$ just the positions of the stones on the board, but he's also storing
$ some higher level 'computed' information, like what groups are on the
$ board, and how many liberties they have.  These are relatively 
$ expensive to compute.  You certainly don't want to copy them for 
$ every move you try.

This is exactly what's going on: I store lots of higher level computed
information, and only a fraction of it changes from move to move.  It
is not intrinsically constant, since most of it *could* change on any
given move; it's just that a move to any particular square on the
board tends to only affect information about nearby objects.  Most of
the information that my program calculates is of this character, and
I'd estimate that (1) >50% of the code in my program is devoted to
updating information of this character, and (2) this is typical of
Go-playing programs.  It's *not* typical of all game-playing programs:
e.g. in Chess-playing programs it seems to be more natural and
efficient to just recalculate things on the fly.

Because of the high proportion of changeable-but-not-changed-this-move
information, solutions like that proposed by Seth Tisue,

+ I realized after sending my last message that actually there is
+ already a way of doing this built into Lisp -- it's not exactly the
+ same thing, but it might be just what you need.  Suppose you're
+ storing your board in the global variable *board*.  If you declare
+ *board* to be "special" (i.e., to have dynamic scope), then saying:
+
+   (let ((*board* <new-value>))
+     ...)

are probably not ideal, because they would (if I understand correctly)
involve an excessive amount of copying.

BTW, it may be that the maintenance problem that I referred to
wouldn't be so bad if I designed an implementation with reversibility
in mind from the very beginning.  The C program where I had the
reversibility problems was originally implemented as a program with
irreversible moves, and only later converted to reversible moves.
Perhaps more of the difficulty that I remember had more to do with
tracking down the last few bits of code which did irreversible
modifications than with absent-mindedly adding new code which did
irreversible modifications.

Whether or not enforcing a requirement that changes be reversible is
necessary, I'm pretty sure that I now know how to solve the problem.
Reversibility can be taken care of with something like the macro given
above, and I know enough about CLOS to be fairly sure that I could use
it to enforce a rule of reversible-modifications-only if I so desired.

Thanks for the help, everybody!

  Bill Newman
  ·······@netcom.com