From: Johan Kullstam
Subject: anaphoric setf?
Date: 
Message-ID: <u1zf9pgbk.fsf@res.raytheon.com>
does anyone have a an anaphoric version of setf?

i'd like to do

(asetf (setf-able-expression with lots of args) (foo it))

where (setf-able-expression with lots of args) is hopefully only
evaluated once and `it' is also (setf-able-expression with lots of
args).

in my actual code which deals with convolutional bit encoders, i have
a local array ww and an index i and i am doing

   (setf (aref ww i) (logxor (logand (aref ww i) -2) (logand k 1)))

perhaps i'd be better off with dpb and byte, but this still would
leave my expression littered with multiple (aref ww i).

does such a thing as asetf exist?

is this functionality covered by something else and i am barking up
the wrong tree?

do i even want to do this?  i.e., is this a bad desire leading down
the road to poor code?

thanks in advance.

-- 
johan kullstam

From: David Bakhash
Subject: Re: anaphoric setf?
Date: 
Message-ID: <cxjzp1xuz23.fsf@acs5.bu.edu>
hey,

why don't you just use let?

(let ((it (aref ww i)))
  (setf (aref ww i) (bar (foo it) (baz it))))

Anyway, that's mostly what the expansion of an anaphoric macro would look like
anyway.

dave
From: Bill Newman
Subject: Re: anaphoric setf?
Date: 
Message-ID: <wnewmanFDJGJM.AxK@netcom.com>
David Bakhash (····@teracorp.com) wrote:
: hey,

: why don't you just use let?

: (let ((it (aref ww i)))
:   (setf (aref ww i) (bar (foo it) (baz it))))

: Anyway, that's mostly what the expansion of an anaphoric macro would look like
: anyway.

I thought the intent was something more like

  (defmacro asetf (place new-value)
    `(setf ,place
           (let ((it ,place))
             ,new-value)))

The difference is clearer in a form like

  (asetf (density (or i-new i) (or j-new j) (or k-new k))
         (max it 0))

when the PLACE form is more complicated, complicated enough that
typing it more than once could encourage errors in creating and
maintaining the code.

I recognize this problem because in my code, I also have
constructs with this property. However, I find that they tend to be
uncommon enough, and of a small enough number of distinct forms, that
I can deal with them by using DEFINE-MODIFY-MACRO to define (e.g.)
MAXF (by analogy with INCF) and then writing

  (maxf (density (or i-new i) (or j-new j) (or k-new k)) 0).

The remaining cases are uncommon enough that I don't mind using

  (symbol-macrolet ((x (density (or i-new i) (or j-new j) (or k-new k))))
    (setf x (max x 0)))

or (in the very few cases where it matters) even

  (symbol-macrolet ((place (density (or i-new i) (or j-new j) (or k-new k))))
    (let ((old-value place))
      (setf place
            ;; some expression which uses OLD-VALUE more than once:
            ..)))

Thus, although I'm reasonably partial to anaphoric macros, I've never
been tempted to use one like ASETF.  YMMV, of course.

  Bill Newman
  ·······@netcom.com
From: Barry Margolin
Subject: Re: anaphoric setf?
Date: 
Message-ID: <Xzxa3.741$KM3.202964@burlma1-snr2>
In article <·················@netcom.com>,
Bill Newman <·······@netcom.com> wrote:
>David Bakhash (····@teracorp.com) wrote:
>: hey,
>
>: why don't you just use let?
>
>: (let ((it (aref ww i)))
>:   (setf (aref ww i) (bar (foo it) (baz it))))
>
>: Anyway, that's mostly what the expansion of an anaphoric macro would look like
>: anyway.
>
>I thought the intent was something more like
>
>  (defmacro asetf (place new-value)
>    `(setf ,place
>           (let ((it ,place))
>             ,new-value)))
>
>The difference is clearer in a form like
>
>  (asetf (density (or i-new i) (or j-new j) (or k-new k))
>         (max it 0))
>
>when the PLACE form is more complicated, complicated enough that
>typing it more than once could encourage errors in creating and
>maintaining the code.

Isn't there also an issue of sub-expressions with side effects?
Presumably,

(asetf (aref ww (incf i)) (1+ it))

should only increment I once.  Properly implementing this requires that
ASETF make use of GET-SETF-EXPANDER.

-- 
Barry Margolin, ······@bbnplanet.com
GTE Internetworking, Powered by BBN, Burlington, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.
Please DON'T copy followups to me -- I'll assume it wasn't posted to the group.
From: Johan Kullstam
Subject: Re: anaphoric setf?
Date: 
Message-ID: <m2wvx1qf66.fsf@sophia.axel.nom>
Barry Margolin <······@bbnplanet.com> writes:

> In article <·················@netcom.com>,
> Bill Newman <·······@netcom.com> wrote:
> >David Bakhash (····@teracorp.com) wrote:
> >: hey,
> >
> >: why don't you just use let?
> >
> >: (let ((it (aref ww i)))
> >:   (setf (aref ww i) (bar (foo it) (baz it))))
> >
> >: Anyway, that's mostly what the expansion of an anaphoric macro would look like
> >: anyway.
> >
> >I thought the intent was something more like
> >
> >  (defmacro asetf (place new-value)
> >    `(setf ,place
> >           (let ((it ,place))
> >             ,new-value)))
> >
> >The difference is clearer in a form like
> >
> >  (asetf (density (or i-new i) (or j-new j) (or k-new k))
> >         (max it 0))
> >
> >when the PLACE form is more complicated, complicated enough that
> >typing it more than once could encourage errors in creating and
> >maintaining the code.

exactly.  i wanted a typo avoidance mechanism.

> Isn't there also an issue of sub-expressions with side effects?
> Presumably,
> 
> (asetf (aref ww (incf i)) (1+ it))
> 
> should only increment I once.  Properly implementing this requires that
> ASETF make use of GET-SETF-EXPANDER.

thanks for all the help.  

after two or three false starts trying to use a (DECLARE (SPECIAL IT))
set to the target and trying to commandeer rplaca, i finally cobbled
one together from paul grahams onlisp stuff.  most of it is
shamelessly ripped off from graham.

i took his _f macro and observed that i'd be mighty close if i passed
(LAMBDA (IT) (FOO ...) PLACE) for OP where (FOO ...) was the
expression with the IT.  then i made simple macro wrapper A1SETF to
stuff the slots.  it was easy to adapt the ABBREVS macro to allow
multiple ASETFs.  i am not sure i really like how IT keeps slaving to
the previous PLACE, but that's how it goes.

;; grouping function
(defun group (source n)
  (if (zerop n) (error "zero length"))
  (labels ((rec (source acc)
             (let ((rest (nthcdr n source)))
               (if (consp rest)
                   (rec rest (cons (subseq source 0 n) acc))
                   (nreverse (cons source acc))))))
    (if source (rec source nil) nil)))

;; setf helper
(defmacro _f (op place &rest args)
  (multiple-value-bind (vars forms var set access) 
                       (get-setf-expansion place)
    `(let* (,@(mapcar #'list vars forms)
            (,(car var) (,op ,access ,@args)))
       ,set)))

;; asetf - allow multiple definitions at one time
(defmacro asetf (&rest implicit-pairs)
  ;; anaphoric asetf for one pair
  (macrolet ((a1setf (place value)
	       `(_f (lambda (it) (,@value)) ,place)))
    ;; unroll for multiple pairs
    `(progn
       ,@(mapcar (lambda (pair) `(a1setf ,@pair))
		 (group implicit-pairs 2)))))

btw is this how one usually uses the MACROLET?  i want to avoid
clutting the namespace with a one-shot macro like A1SETF.


now i can do stuff like

USER(29): (setq *foo* '#(10 11 12 13))
#(10 11 12 13)
USER(30): (asetf (aref *foo* 3) (- it 10))
3
USER(31): *foo*
#(10 11 12 3)


this could have been done with decf, but what about doubling something
with (* it 2)?  i kind of like it.

here's a multi-shot.  i return the last thing set.

USER(32): (asetf (aref *foo* 0) 3
		 (aref *foo* 1) (* it it))
121
USER(33): *foo*
#(3 121 12 3)


ok let us check for single eval and side-effect sanity

USER(34): (setq *foo* '#(10 11 12 13))
#(10 11 12 13)
USER(35): (setq i -1)
-1
USER(36): (asetf (aref *foo* (incf i 1)) (- it 10))
0
USER(37): *foo*
#(0 11 12 13)
USER(38): i
0
USER(39): (asetf (aref *foo* (incf i 1)) (- it 10))
1
USER(40): *foo*
#(0 1 12 13)
USER(41): i
1

notice how the incf only gets eval'd *once*.

-- 
J o h a n  K u l l s t a m
[········@ne.mediaone.net]
Don't Fear the Penguin!
From: Arthur Lemmens
Subject: Re: anaphoric setf?
Date: 
Message-ID: <376AC428.1F7E22E1@simplex.nl>
Barry Margolin wrote:
> 
> Isn't there also an issue of sub-expressions with side effects?
> Presumably,
> 
> (asetf (aref ww (incf i)) (1+ it))
> 
> should only increment I once.  Properly implementing this requires that
> ASETF make use of GET-SETF-EXPANDER.

Yes (only it's called GET-SETF-EXPANSION nowadays).
Here's what I use. It's based on Paul Graham's version.
I can't say I use it very often, but when I do, I'm glad to have it.

(defmacro asetf (place &rest args)
  (multiple-value-bind (temp-vars temp-vals access-var set access-val)
      (get-setf-expansion place)
    `(let* (,@(mapcar #'list temp-vars temp-vals)
            (,(car access-var) (let ((it ,access-val)) ,@args)))
       ,set)))


;; EXAMPLES is a simple macro to verify that everything is working 
;; as intended.

(examples (ASETF)
  (=> (let ((nums (list 1 2 3)))
        (asetf (second nums) (* it it))
        nums)
      '(1 4 3))
  ;; Nesting ASETF is no problem.
  (=> (let ((nums (list 10 20 30))) 
        (asetf (first nums) 
               (+ (asetf (second nums) (- it 1))
                  it)) 
        nums)
      '(29 19 30))
  ;; Side effects are executed as often as they should be.
  (=> (let ((ww #(1 2 3 4)) 
            (i 0))
        (values (asetf (aref ww (incf i)) (/ it 7)) 
                i 
                ww))
      2/7
      1              ; i is incremented only once
      #(1 2/7 3 4)   ; the second elt of ww is modified
      ))

Arthur Lemmens
From: John Wiseman
Subject: Re: anaphoric setf?
Date: 
Message-ID: <arx674lcjw0.fsf@gargoyle.cs.uchicago.edu>
Johan Kullstam <········@ne.mediaone.net> writes:

> i'd like to do
> 
> (asetf (setf-able-expression with lots of args) (foo it))
> 
> where (setf-able-expression with lots of args) is hopefully only
> evaluated once and `it' is also (setf-able-expression with lots of
> args).

Just to be clear, (setf-able-expression with lots of args) is not
evaluated twice in the expression

  (setf (setf-able-expression with lots of args)
        (foo (setf-able-expression with lots of args)))

because it is equivalent to something like

  (set-setf-able-expression (setf-able-expression with lots of args)
                            with lots of args)

(setf-able-expression ...) is evaluated once, and each argument in
"lots of args" is evaluated twice.


So instead of writing something like

  (setf (aref (a 0) (b 1) (c 2))
        (list (aref (a 0) (b 1) (c 2))
              (aref (a 0) (b 1) (c 2))))

you want to be able to write


  (asetf (aref (a 0) (b 1) (c 2))
         (list it it))

which would become something like

  (let ((#:v1 (a 0))
        (#:v2 (b 1))
        (#:v3 (c 2)))
    (let ((it (aref #:v1 #:v2 #:v3)))
      (setf (aref #:v1 #:v2 #:v3) (list it it))))


How about


(defmacro asetf (place value)
  (destructuring-bind (place-fn &rest place-args) place
    (let ((place-vars (mapcar #'(lambda (arg)
                                  (declare (ignore arg))
                                  (gensym))
                              place-args)))
      `(let (,@(mapcar #'list
                       place-vars
                       place-args))
         (let ((it (,place-fn ,@place-vars)))
           (setf (,place-fn ,@place-vars) ,value))))))


I don't think there is anything particularly bad with doing this.  I
don't use anaphoric macros, but that's just my personal style.

If you're worried about performance, anaphora won't help you in the
situation where you have to do a lot of work to find the thing whose
value is being looked up and updated.  For example,

  (asetf (expensive-foo-search my-foo) (+ it 1))

still has to do the work of searching for foo twice: once to get the
value, once to set the value.  In this case it's better to forget the
setf idiom and just do

  (foo-increment my-foo 1)


John Wiseman
From: Kent M Pitman
Subject: Re: anaphoric setf?
Date: 
Message-ID: <sfwbtedtd6j.fsf@world.std.com>
Johan Kullstam <········@ne.mediaone.net> writes:

> does anyone have a an anaphoric version of setf?
> 
> i'd like to do
> 
> (asetf (setf-able-expression with lots of args) (foo it))
> 
> where (setf-able-expression with lots of args) is hopefully only
> evaluated once and `it' is also (setf-able-expression with lots of
> args).

I know it's not what you're asking, but this is the right time to
mention define-modify-macro.  It offers some cool features that 
are really quite useful in this context.  For example, you could
write a (foof x . other-args) that was (setf x (foo x . other-args)).

For example, I quite often create NREVERSEF and MAXF and MINX and
NCONCF and APPENDF as helpers.  They are each one-liners to write.
CLHS contains a number of examples.

And, of course, it's pretty easy to see how to generalize this to
something that uses FUNCALL ...