From: Vladimir Zolotykh
Subject: conditional setq ?
Date: 
Message-ID: <3E329432.7040602@eurocom.od.ua>
Hi

My intention was to set either A or B depending on C. The following
code which was seemed to me safe enough doesn't work.

(defun foo (c)
   (let ((a 1) (b 2))
     (set (if c 'a 'b) 10)
     (list a b)))

And it shouldn't, because SET uses SYMBOL-VALUE.  I wonder whether
there is a way to say

   (if c (setq a 10) (setq b 10))

more elegant.

Thanks in advance

-- 
Vladimir Zolotykh

From: Paul F. Dietz
Subject: Re: conditional setq ?
Date: 
Message-ID: <t_KcnVQjG98eCq-jXTWcpQ@dls.net>
Vladimir Zolotykh wrote:
> Hi
> 
> My intention was to set either A or B depending on C. The following
> code which was seemed to me safe enough doesn't work.
> 
> (defun foo (c)
>   (let ((a 1) (b 2))
>     (set (if c 'a 'b) 10)
>     (list a b)))
> 
> And it shouldn't, because SET uses SYMBOL-VALUE.  I wonder whether
> there is a way to say
> 
>   (if c (setq a 10) (setq b 10))
> 
> more elegant.

You'll want to define a setf expander for IF.  See DEFINE-SETF-EXPANDER
in the hyperspec.

	Paul
From: Steven M. Haflich
Subject: Re: conditional setq ?
Date: 
Message-ID: <3E3349B0.2050607@alum.mit.edu>
Paul F. Dietz wrote:

> You'll want to define a setf expander for IF.  See DEFINE-SETF-EXPANDER
> in the hyperspec.

Yeah, and make sure your expander handles the multiple-value case
correctly, otherwise it wouldn't be correct.

I'll bet there is not a single reader of this list who can code this
definition correctly in portable Common Lisp.  Any takers?
From: Nils Goesche
Subject: Re: conditional setq ?
Date: 
Message-ID: <87wuks4llg.fsf@darkstar.cartan>
"Steven M. Haflich" <·················@alum.mit.edu> writes:

> Paul F. Dietz wrote:
> 
> > You'll want to define a setf expander for IF.  See DEFINE-SETF-EXPANDER
> > in the hyperspec.
> 
> Yeah, and make sure your expander handles the multiple-value
> case correctly, otherwise it wouldn't be correct.
> 
> I'll bet there is not a single reader of this list who can code
> this definition correctly in portable Common Lisp.  Any takers?

Hm.  How about this:

(define-setf-expander if (test then else &environment env)
  (multiple-value-bind (then-temps then-vals then-stores
                                   then-store-form then-access-form)
      (get-setf-expansion then env)
    (multiple-value-bind (else-temps else-vals else-stores
                                     else-store-form else-access-form)
        (get-setf-expansion else env)
      (let ((test-var (gensym))
            (stores (loop repeat (max (length then-stores) (length else-stores))
                          collect (gensym))))
        (values (cons test-var (append then-temps else-temps))
                (cons test (append (mapcar (lambda (form)
                                             `(when ,test-var
                                                ,form))
                                           then-vals)
                                   (mapcar (lambda (form)
                                             `(unless ,test-var
                                                ,form))
                                           else-vals)))
                stores
                `(if ,test-var
                     (let* ,(mapcar #'list then-stores stores)
                       ,then-store-form)
                   (let* ,(mapcar #'list else-stores stores)
                     ,else-store-form))
                `(if ,test-var
                     (let* ,(mapcar #'list then-stores stores)
                       ,then-access-form)
                   (let* ,(mapcar #'list else-stores stores)
                     ,else-access-form)))))))

I barely tested it... please don't kill me.

Regards,
-- 
Nils G�sche
Ask not for whom the <CONTROL-G> tolls.

PGP key ID #xD26EF2A0
From: Paul F. Dietz
Subject: Re: conditional setq ?
Date: 
Message-ID: <3E336A58.3030204@dls.net>
Nils Goesche wrote:

> I barely tested it... please don't kill me.
> 
> Regards,

Doesn't look quite right:
* (macroexpand '(push 'a (if x y z)))

(LET* ((#:G858 'A)
        (#:G856 X)
        (#:G857
         (CONS #:G858
               (IF #:G856
                   (LET* ((#:G854 #:G857))  ;; unbound
                     Y)
                   (LET* ((#:G855 #:G857))  ;; unbound
                     Z)))))
   (IF #:G856
       (LET* ((#:G854 #:G857))
         (SETQ Y #:G854))
       (LET* ((#:G855 #:G857))
         (SETQ Z #:G855))))
From: Nils Goesche
Subject: Re: conditional setq ?
Date: 
Message-ID: <87smvg4ie2.fsf@darkstar.cartan>
"Paul F. Dietz" <·····@dls.net> writes:

> Doesn't look quite right:
> * (macroexpand '(push 'a (if x y z)))
> 
> (LET* ((#:G858 'A)
>         (#:G856 X)
>         (#:G857
>          (CONS #:G858
>                (IF #:G856
>                    (LET* ((#:G854 #:G857))  ;; unbound
>                      Y)
>                    (LET* ((#:G855 #:G857))  ;; unbound
>                      Z)))))
>    (IF #:G856
>        (LET* ((#:G854 #:G857))
>          (SETQ Y #:G854))
>        (LET* ((#:G855 #:G857))
>          (SETQ Z #:G855))))

Darn, I posted too fast.  But if my new version isn't correct
I'll give up:

(define-setf-expander if (test then else &environment env)
  (multiple-value-bind (then-temps then-vals then-stores
                                   then-store-form then-access-form)
      (get-setf-expansion then env)
    (multiple-value-bind (else-temps else-vals else-stores
                                     else-store-form else-access-form)
        (get-setf-expansion else env)
      (let ((test-var (gensym))
            (stores (loop repeat (max (length then-stores) (length else-stores))
                          collect (gensym))))
        (values (cons test-var (append then-temps else-temps))
                (cons test (append (mapcar (lambda (form)
                                             `(when ,test-var
                                                ,form))
                                           then-vals)
                                   (mapcar (lambda (form)
                                             `(unless ,test-var
                                                ,form))
                                           else-vals)))
                stores
                `(if ,test-var
                     (let ,(mapcar #'list then-stores stores)
                       ,then-store-form)
                   (let ,(mapcar #'list else-stores stores)
                     ,else-store-form))
                `(if ,test-var
                     ,then-access-form
                   ,else-access-form))))))

Regards,
-- 
Nils G�sche
Ask not for whom the <CONTROL-G> tolls.

PGP key ID #xD26EF2A0
From: Steven M. Haflich
Subject: Re: conditional setq ?
Date: 
Message-ID: <3E33F98B.9090805@alum.mit.edu>
Nils Goesche wrote:

> Darn, I posted too fast.  But if my new version isn't correct
> I'll give up:

I haven't checked your proposed definition, but I already _know_ it
isn't correct -- chuckle chuckle -- and I knew it wouldn't be when
I posted my challenge.  I've played with the list a little here, and
certainly don't want to continue, so I'll explain:  _Any_
definition on cl:if as a setf expander runs afoul of 11.1.2.1.2
"Constraints on the COMMON-LISP Package for Conforming Programs"
bullet 13:

   <http://www.lispworks.com/reference/HyperSpec/Body/11_abab.htm>

Now, it appears that it would be conforming for an _implementation_
to provide such a definition, but of course, a portable program cannot
rely upon such a language extension.  So I'm afraid the result of
defining your setf expander will be "undefined consequences".

On the other hand, this example is (as someone else has already pointed
out) a very good exercise in writing and understanding setf expanders.
I haven't yet examined your solution in that spirit, but will now do so.
There is no reason to expect that it won't _otherwise_ be correct :-).
From: Nils Goesche
Subject: Re: conditional setq ?
Date: 
Message-ID: <87wukrubl4.fsf@darkstar.cartan>
"Steven M. Haflich" <·················@alum.mit.edu> writes:

> Nils Goesche wrote:
> 
> > Darn, I posted too fast.  But if my new version isn't correct
> > I'll give up:
> 
> I haven't checked your proposed definition, but I already _know_ it
> isn't correct -- chuckle chuckle --

>    <http://www.lispworks.com/reference/HyperSpec/Body/11_abab.htm>

Well, I didn't use either DEFSETF or DEFINE-SETF-METHOD, did I? :-)

> On the other hand, this example is (as someone else has already
> pointed out) a very good exercise in writing and understanding
> setf expanders.  I haven't yet examined your solution in that
> spirit, but will now do so.  There is no reason to expect that
> it won't _otherwise_ be correct :-).

Sure, please do that.  I believe it to be correct, but my
understanding of DEFINE-SETF-EXPANDER is still a bit... shaky.

Regards,
-- 
Nils G�sche
Ask not for whom the <CONTROL-G> tolls.

PGP key ID #xD26EF2A0
From: Kalle Olavi Niemitalo
Subject: Re: conditional setq ?
Date: 
Message-ID: <87u1fs0xa8.fsf@Astalo.y2000.kon.iki.fi>
Nils Goesche <···@cartan.de> writes:

> Well, I didn't use either DEFSETF or DEFINE-SETF-METHOD, did I? :-)

If you had used DEFINE-SETF-METHOD, what would the definition
have looked like?  ;-)

Seriously, the DEFINE-SETF-METHOD reference in 11.1.2.1.2 must be
an error.  See the issue SETF-METHOD-VS-SETF-METHOD.
<http://www.lispworks.com/reference/HyperSpec/Issues/iss308_w.htm>
From: Pascal Bourguignon
Subject: Re: conditional setq ?
Date: 
Message-ID: <87hebv614a.fsf@thalassa.informatimago.com>
"Steven M. Haflich" <·················@alum.mit.edu> writes:

> Nils Goesche wrote:
> 
> > Darn, I posted too fast.  But if my new version isn't correct
> > I'll give up:
> 
> I haven't checked your proposed definition, but I already _know_ it
> isn't correct -- chuckle chuckle -- and I knew it wouldn't be when
> I posted my challenge.  I've played with the list a little here, and
> certainly don't want to continue, so I'll explain:  _Any_
> definition on cl:if as a setf expander runs afoul of 11.1.2.1.2
> "Constraints on the COMMON-LISP Package for Conforming Programs"
> bullet 13:
> 
>    <http://www.lispworks.com/reference/HyperSpec/Body/11_abab.htm>

That's  a  problem  with  specifications  that don't  want  to  commit
themselves to anything. (Common-Lisp falls into this category IMHO).

Because obviously, now you must define your own lisp:

    (defmacro my-if (condition if-true if-false)
       `(if ,condition ,if-true ,if-false))

just to be able to do a (defsetf my-if ...)
and the same for all the rest.


For example  recently I had  to reimplement FIND,  because Common-Lisp
does  not specify  what  shall be  the  first parameter  of the  :test
function and what shall be the second.


If course,  it's nice when you  can write programs that  don't need to
make any assumptions  on the underlying system and  libraries.  But do
you know many programs of this kind?


Historically, I  understand that  since Common-Lisp came  from merging
pre-existing lisp, it  had to be the greatest  common denominator, but
nowadays, do we  see that much variability in  implementations that we
could not have a more specific specification?

-- 
__Pascal_Bourguignon__                   http://www.informatimago.com/
----------------------------------------------------------------------
There is a fault in reality. Do not adjust your minds. -- Salman Rushdie
From: Matthew Danish
Subject: Re: conditional setq ?
Date: 
Message-ID: <20030126165449.I27240@lain.cheme.cmu.edu>
On Sun, Jan 26, 2003 at 10:40:37PM +0100, Pascal Bourguignon wrote:
> For example  recently I had  to reimplement FIND,  because Common-Lisp
> does  not specify  what  shall be  the  first parameter  of the  :test
> function and what shall be the second.

See CLHS 17.2

-- 
; Matthew Danish <·······@andrew.cmu.edu>
; OpenPGP public key: C24B6010 on keyring.debian.org
; Signed or encrypted mail welcome.
; "There is no dark side of the moon really; matter of fact, it's all dark."
From: Kent M Pitman
Subject: Re: conditional setq ?
Date: 
Message-ID: <sfwsmve76ve.fsf@shell01.TheWorld.com>
Pascal Bourguignon <···@informatimago.com> writes:

> >    <http://www.lispworks.com/reference/HyperSpec/Body/11_abab.htm>
> 
> That's  a  problem  with  specifications  that don't  want  to  commit
> themselves to anything. (Common-Lisp falls into this category IMHO).

Nonsense.

The spec is quite legitimately protecting users from clobbering each
other by relying upon custom extensions which you might imagine are
all compatible, but which in fact might not be.  Since CL:IF is a shared
symbol, all clients of the CL package are at risk of redefining IF's SETF
if you allow such, and the redefinitions mgiht hurt portable code.  So it
is forbidden.

By contrast, for each implementation there is only one implementation.
That may seem obvious, but its consequence is that allowing an
implementation to experiment with an extension in this position is not
a problem.  If no user of portable code can rely on it, the extension
is compatible.  If users cannot clobber it without being
non-conforming, the extension is "safe".

There are several SETF's that some implementations provide and some do not.
SETF of SYMBOL-PACKAGE of a symbol is one.  SETF of the pathname slots is
another cluster of them; in some implementations, pathnames are 'interned'
(EQ-ified when EQUAL), and so a SETF function would be a disaster, while in
other implementations they are not and in some such implementations it is
permissible to assign the slot.  (In general, I think it's a bad idea to
set pathname slots, but, for better or worse, no one elected me king of
everyone...)
From: Paul Dietz
Subject: Re: conditional setq ?
Date: 
Message-ID: <3E359594.95213C80@motorola.com>
Kent M Pitman wrote:

> The spec is quite legitimately protecting users from clobbering each
> other by relying upon custom extensions which you might imagine are
> all compatible, but which in fact might not be.  Since CL:IF is a shared
> symbol, all clients of the CL package are at risk of redefining IF's SETF
> if you allow such, and the redefinitions mgiht hurt portable code.  So it
> is forbidden.

If the user wishes to do this portably they can shadow IF in their
packages, and define suitable macro/expander/etc. on that symbol.

	Paul
From: Kent M Pitman
Subject: Re: conditional setq ?
Date: 
Message-ID: <sfwy956xkuh.fsf@shell01.TheWorld.com>
Paul Dietz <············@motorola.com> writes:

> Kent M Pitman wrote:
> 
> > The spec is quite legitimately protecting users from clobbering each
> > other by relying upon custom extensions which you might imagine are
> > all compatible, but which in fact might not be.  Since CL:IF is a shared
> > symbol, all clients of the CL package are at risk of redefining IF's SETF
> > if you allow such, and the redefinitions mgiht hurt portable code.  So it
> > is forbidden.
> 
> If the user wishes to do this portably they can shadow IF in their
> packages, and define suitable macro/expander/etc. on that symbol.

Certainly.  But my remarks were in particular defense of making restrictions
on the CL package.  Obviously, I hope, if you shadow something in the CL
package you are no longer under those restrictions.

Indeed, one reason we felt comfortable placing these restrictions was the
easy availability of shadowing capabilities.
From: Sam Steingold
Subject: Re: conditional setq ?
Date: 
Message-ID: <m31y2v5wgf.fsf@loiso.podval.org>
> * In message <················@alum.mit.edu>
> * On the subject of "Re: conditional setq ?"
> * Sent on Sat, 25 Jan 2003 18:36:32 -0800
> * Honorable "Steven M. Haflich" <·················@alum.mit.edu> writes:
>
> Paul F. Dietz wrote:
> 
> > You'll want to define a setf expander for IF.  See DEFINE-SETF-EXPANDER
> > in the hyperspec.
> 
> Yeah, and make sure your expander handles the multiple-value case
> correctly, otherwise it wouldn't be correct.
> 
> I'll bet there is not a single reader of this list who can code this
> definition correctly in portable Common Lisp.  Any takers?

CLISP sources (GNU GPL):

(define-setf-expander IF (condition t-form f-form &environment env)
  (let ((conditionvar (gensym)))
    (multiple-value-bind (T-SM1 T-SM2 T-SM3 T-SM4 T-SM5)
        (get-setf-expansion t-form env)
      (multiple-value-bind (F-SM1 F-SM2 F-SM3 F-SM4 F-SM5)
          (get-setf-expansion f-form env)
        (unless (eql (length T-SM3) (length F-SM3))
          (error 'program-error
            "SETF place ~S expects different numbers of values in the true and false branches (~D vs. ~D values)."
            (list 'IF condition t-form f-form) (length T-SM3) (length F-SM3)))
        (values
          `(,conditionvar
            ,@T-SM1
            ,@F-SM1)
          `(,condition
            ,@(mapcar #'(lambda (x) `(IF ,conditionvar ,x)) T-SM2)
            ,@(mapcar #'(lambda (x) `(IF (NOT ,conditionvar) ,x)) F-SM2))
          T-SM3
          `(IF ,conditionvar ,T-SM4 ,(sublis (mapcar #'cons F-SM3 T-SM3) F-SM4))
          `(IF ,conditionvar ,T-SM5 ,F-SM5))))))


-- 
Sam Steingold (http://www.podval.org/~sds) running RedHat8 GNU/Linux
<http://www.camera.org> <http://www.iris.org.il> <http://www.memri.org/>
<http://www.mideasttruth.com/> <http://www.palestine-central.com/links.html>
Oh Lord, give me the source code of the Universe and a good debugger!
From: Frode Vatvedt Fjeld
Subject: Re: conditional setq ?
Date: 
Message-ID: <2hof65mi0s.fsf@vserver.cs.uit.no>
Vladimir Zolotykh <······@eurocom.od.ua> writes:

> I wonder whether there is a way to say
>
>    (if c (setq a 10) (setq b 10))
>
> more elegant.

Why do you think there should be a different way to say this? You
could write a setf expander for if, but I don't think it will buy you
enough in terms of expressiveness or elegancy to justify itself.

-- 
Frode Vatvedt Fjeld
From: Paul F. Dietz
Subject: Re: conditional setq ?
Date: 
Message-ID: <lUadnUggptMINK-jXTWc3A@dls.net>
Frode Vatvedt Fjeld wrote:

> Why do you think there should be a different way to say this? You
> could write a setf expander for if, but I don't think it will buy you
> enough in terms of expressiveness or elegancy to justify itself.

It's a reasonable thing to want to do, in my opinion.

	Paul
From: Vladimir Zolotykh
Subject: Re: conditional setq ?
Date: 
Message-ID: <3E32A6C2.2060105@eurocom.od.ua>
Frode Vatvedt Fjeld wrote:

> Why do you think there should be a different way to say this? You
> could write a setf expander for if, but I don't think it will buy you
> enough in terms of expressiveness or elegancy to justify itself.


My be it won't but it'll be useful exercise anyway.

-- 
Vladimir Zolotykh
From: Kaz Kylheku
Subject: Re: conditional setq ?
Date: 
Message-ID: <cf333042.0301251615.442ea09c@posting.google.com>
Vladimir Zolotykh <······@eurocom.od.ua> wrote in message news:<················@eurocom.od.ua>...
> Hi
> 
> My intention was to set either A or B depending on C. The following
> code which was seemed to me safe enough doesn't work.
> 
> (defun foo (c)
>    (let ((a 1) (b 2))
>      (set (if c 'a 'b) 10)
>      (list a b)))
> 
> And it shouldn't, because SET uses SYMBOL-VALUE.

There is no way to set a lexical variable using its symbol. The
relationship between a lexical variable and the symbol which names it
exists only at compile time, just like in languages such as C, Pascal,
Algol and so on.

Once a closure is compiled, there may remain absolutely no symbolic
references to its lexical variables, only offsets into some vector of
bindings, or region of the stack frame.

> I wonder whether
> there is a way to say
> 
>    (if c (setq a 10) (setq b 10))
> 
> more elegant.

If you want elegance, then specify what the elegant form should look
like, and then write a macro which transforms from that form to the
original inelegant one.

The most abstract form would disguise the entire mechanism, such that
it would have only these elements: the name of the operator, the two
symbols to be conditionally assigned, the condition for selecting
between them and the new value. E.g.

  (set-if expr a b 10)

So now you just need a SET-IF macro which pulls out these four
parameters, and substitutes them into an IF form to produce (if expr
(setq a 10) (setq b 10)).

This is not quite right; you must evaluate the 10 only once, so a
gensym is called for. The translation you want is:

   (let ((#:g0025 10))  ;; Obscure Godel, Escher, Bach reference.
     (if expr (setq a #:unique) (setq b #:unique))

Nope, still not right, because now the order of evaluation is screwed
between the expr and the new value. Better make it:

   (let ((#:g0026 expr)
         (#:g0027 10))
     (if #:g0026 (setq a #:g0027) (setq b #:g0027)))

So now to write the macro:

   (defmacro set-if (condition-expr left-sym right-sym value-expr)
     (let ((cond-sym (gensym "CONDITION-"))
           (new-val-sym (gensym "NEW-VALUE-")))
       `(let ((,cond-sym ,condition-expr)
              (,new-val-sym ,value-expr))
          (if ,cond-sym 
            (setq ,left-sym ,new-val-sym)
            (setq ,right-sym ,new-val-sym)))))
From: Sam Steingold
Subject: Re: conditional setq ?
Date: 
Message-ID: <m3znppp3vi.fsf@loiso.podval.org>
> * In message <················@eurocom.od.ua>
> * On the subject of "conditional setq ?"
> * Sent on Sat, 25 Jan 2003 15:42:10 +0200
> * Honorable Vladimir Zolotykh <······@eurocom.od.ua> writes:
>
> My intention was to set either A or B depending on C. The following
> code which was seemed to me safe enough doesn't work.
> 
> (defun foo (c)
>    (let ((a 1) (b 2))
>      (set (if c 'a 'b) 10)
>      (list a b)))
> 
> And it shouldn't, because SET uses SYMBOL-VALUE.  I wonder whether
> there is a way to say
> 
>    (if c (setq a 10) (setq b 10))

in CLISP you can do

(setf (if c a b) 10)

see <http://clisp.cons.org/impnotes/data.html#setf> for other
additional places and src/places.lisp for the sources.



-- 
Sam Steingold (http://www.podval.org/~sds) running RedHat8 GNU/Linux
<http://www.camera.org> <http://www.iris.org.il> <http://www.memri.org/>
<http://www.mideasttruth.com/> <http://www.palestine-central.com/links.html>
main(a){printf(a,34,a="main(a){printf(a,34,a=%c%s%c,34);}",34);}
From: Pascal Bourguignon
Subject: Re: conditional setq ?
Date: 
Message-ID: <87bs256v9i.fsf@thalassa.informatimago.com>
Vladimir Zolotykh <······@eurocom.od.ua> writes:

> Hi
> 
> My intention was to set either A or B depending on C. The following
> code which was seemed to me safe enough doesn't work.
> 
> (defun foo (c)
>    (let ((a 1) (b 2))
>      (set (if c 'a 'b) 10)
>      (list a b)))
> 
> And it shouldn't, because SET uses SYMBOL-VALUE.  I wonder whether
> there is a way to say

See what Hyperspec has to say about set: 

    set cannot change the value of a lexical variable.

So it would work on global variables:

[1]> (setq c t)
T
[2]> (set (if c 'a 'b) :toto)
:TOTO
[3]> a
:TOTO
[4]> b

*** - EVAL: variable B has no value
1. Break [5]> 


[17]> (defvar va 1)
VA
[18]> (defvar vb 2)
VB
[19]> (defun foo (c)
[19]>   (let (v)
[19]>     (setq v  (if c 'va 'vb))
[19]>     (set v 10)
[19]>     (list va vb)))
FOO
[20]> (values (foo t) (foo nil))
(10 2) ;
(10 10)


You must declare the variables special to be able to change them with set:

[27]> (defun foo (c)
[27]>     (let ((a 1) (b 2))
[27]>       (declare (special a) (special b))
[27]>       (set (if c 'a 'b) 10)
[27]>       (list a b)))
FOO
[28]> (values (foo t) (foo nil))
(10 2) ;
(1 10)



-- 
__Pascal_Bourguignon__                   http://www.informatimago.com/
----------------------------------------------------------------------
There is a fault in reality. Do not adjust your minds. -- Salman Rushdie
From: sv0f
Subject: Re: conditional setq ?
Date: 
Message-ID: <none-2701031037490001@129.59.212.53>
In article <················@eurocom.od.ua>, Vladimir Zolotykh
<······@eurocom.od.ua> wrote:

>I wonder whether
>there is a way to say
>
>   (if c (setq a 10) (setq b 10))
>
>more elegant.

What follows is not necessarily more elegant, but it hides the IF
in one level of list structure:

     (setq a (if c 10 (progn (setq b 10) a)))

As in:

     ? (let ((a 20)
             (b 20)
             (c t))
         (setq a (if c 10 (progn (setq b 10) a)))  ; critical line
         (format t "~&A: ~A~%B: ~A~%C: ~A" a b c))
      A: 10
      B: 20
      C: T
      NIL
     ? (let ((a 20)
             (b 20)
             (c nil))
         (setq a (if c 10 (progn (setq b 10) a)))  ; critical line
         (format t "~&A: ~A~%B: ~A~%C: ~A" a b c))
      A: 20
      B: 10
      C: NIL
      NIL
     ?