From: Erann Gat
Subject: A modest proposal (long)
Date: 
Message-ID: <gat-2902001653240001@milo.jpl.nasa.gov>
I've been watching the recent threads on special variables, top-level
setq-s and the like, and I've come to the conclusion that the current
situation is badly broken.  I have a proposal on how to fix it that I'd
like some feedback on.

The intractable problem is that beginners are chronically confused by
the fact that Lisp does not make an adequate syntactic distinction
between two completely different ways of binding variables.  Imagine
you are reading some code and you encounter the following two functions:

(defun foo (x) (blarg x))

(defun baz (y) (blarg y))

Do FOO and BAZ do the same thing?  Well, they might or they might not.
It depends.  It depends on whether X or Y have been DEFVARed.  It depends
on whether there are any free references to X or Y in any function called
by BLARG.  It depends on whether you are trying to write thread-safe code.
It depends on whether performance differences matter.  It depends on whether
your code is interpreted or compiled.  And if you want to explain the
reasons it depends on all these things you have to start talking about
the differences between symbols and variables, what bindings are, and
that there's nothing at all special about "special" variables, it's just
an ancient piece of Lisp terminological baggage that means nothing more
than "dynamic scope."

A beginner's initiation into this state of affairs invariably comes when
he or she one day as an expedient types (defvar x 1) and then spends the
rest of the day (or week) trying to figure out why her code is suddenly
exhibiting mysterious bugs.  The admonition to always use *...* notation
for DAFVARed variables is a temporary fix, but it generally takes a very
long time for a typical programmer to wrap their brains around what is
really going on.

The problem is pervasive and subtle.  Consider:

(funcall (lambda (x y) (lambda () ... x ... y ...)) 1 2)

Does this return a lexical closure over X and Y?  Well, it might, or it
might not.  It depends.

Now, this has not been much of an issue because artificially separating
the name spaces of lexical and dynamic variables using the *...* convention
generally works to keep the problem at bay.  But the trouble is that this
solution only works if you use it, and you can only use it if you are
aware of it.  And even if you are aware of it, your collaborator might
not be.  *You* might not have DEFVARed X, but how do you know that Joe
didn't?

The solution to this problem is to change the language so that the
distinction between dynamic and lexical bindings is locally manifested.
This is technically simple, but politically complex because it means
either adding some kind of lexical declaration or getting rid of pervasive
SPECIAL declarations (e.g. getting rid of DEFVAR, (PROCLAIM (SPECIAL ...))
etc.)  My personal preference is the latter.  Top-level declarations that
radically change the semantics of code in ways that are not lexically
apparent are EVIL!

Even local special declarations are IMO evil.  The semantics of a piece
of code ought not to depend on forward references.  It's also very much
against the spirit of a declaration.  Declarations are for providing extra
information for the compiler.  They are not for changing the semantics of
the program.  It should be possible to remove all declarations without
changing anything about the program except how fast it runs.

The solution is obvious.  Special variables are nothing more than the
symbol-value slot of some symbol.  Why not make that simple fact manifest
itself in the syntax?  For example:

(let ( (x 1)                   ; A lexical binding
       ((symbol-value x) 2) )  ; A dynamic binding

While we're at it we could fold in the binding of multiple values and
destructing into one uniform syntax:

(superlet ( (x 1)                   ; A lexical binding (guaranteed)
            ((symbol-value x) 2)    ; == (let ((x 2)) (declare (special x))
            ((values a b c) (foo))  ; == (multiple-value-bind (a b c) (foo)
            ((values a (symbol-value b) c) (baz))
                                    ; As above, but with (declare (special b))
            ((a b c) (foo)) )       ; A DESTRUCTING-BIND

A simple reader macro helps make things a lot less wordy:

$x == (symbol-value 'x)

So now we can write:

(let ( (x 1) ($y 2) ) ; X is a lexical binding, Y is a dynamic binding

This would work at top-level too:

(setf $x 1) ; Set the global X with no warnings and no semantic ambiguity
(setf x 1) --> Warning! No lexical variable named X visible here.  Setting
$X instead.

To implement this proposal completely requires the cooperation of Lisp
implementors because you have to change the way lambda lists are
processed.  But once that's done you can write (lambda (x $y) ...)
instead of (lambda (x y) (declare (special y)) ...), or
(multiple-value-bind (x $y) (foo) ...) instead of (multiple-value-bind
(x y) (foo) (declare (special y)) ...) or (defun foo (x $y) ...) instead
of (defun foo (x y) (declare (special y))  ...)

As a prototype I have implemented a macro called BIND that works as
described above.  BIND binds lexical and dynamic variables, and handles
multiple values and destructuring.  It also uses a paren-less LOOP-like
syntax.  I present it as both an illustration of how simple my proposal
would be to implement properly, and as an illustration of how easy it is
to change Lisp completely within the standard.

The syntax for BIND is:

(BIND var [=] value [and] ... in &rest body)

var : symbol | (symbol-value symbol) | (values var var ...) | list

Keywords in square brackets are optional.

Example: (BIND x = 1 and (z ($y) q) = (foo) and (values $a b c) = (baz) in ...)

expands to:

(let ( (x 1) )
  (destructuring-bind (z (y) q) (foo)
    (declare (special y))
    (multiple-value-bind (a b c) (baz)
       (declare (special a))
       ...

I conjecture that beginners at least will find BIND easier to deal with
than the things it replaces.

Erann Gat
···@jpl.nasa.gov
---


(set-macro-character #\$
                     (lambda (s c)
                       (declare (ignore c))
                       (if (whitespacep (peek-char nil s))
                         '|$|
                         `(%symval ,(read s))))
                     t)

(defmacro %symval (x) `(symbol-value ',x))

(defun process-vartree (vl)
  (let ( (specials '()) )
    (setf vl
          (iterate loop1 ( (v vl) )
            (cond ( (atom v) v )
                  ( (eq (car v) '%symval)
                    (push (second v) specials)
                    (second v) )
                  (t (cons (loop1 (car v)) (loop1 (cdr v)))))))
    (values vl specials)))

(defmacro bind (&rest forms)
  (cond ( (null forms) (error "Missing IN keyword") )
        ( (eq (car forms) 'in)
          `(progn ,@(cdr forms)) )
        ( (eq (car forms) 'and)
          `(bind ,@(cdr forms)) )
        (t (let ( (var (pop forms))
                  (val (pop forms)) )
             (if (eq val '=) (setf val (pop forms)))
             (cond
              ( (atom var)
                `(let ( (,var ,val) ) (bind ,@forms)) )
              ( (eq (car var) '%symval)
                (setf var (second var))
                `(let ( (,var ,val) )
                   (declare (special ,var))
                   (bind ,@forms)) )
              ( (eq (car var) 'values)
                (receive (vars specials) (process-vartree (cdr var))
                  `(multiple-value-bind ,vars ,val
                     (declare (special ,@specials))
                     (bind ,@forms))) )
              (t (receive (vars specials) (process-vartree var)
                   `(destructuring-bind ,vars ,val
                      (declare (special ,@specials))
                      (bind ,@forms)))))))))

#|
; Example:
(defun baz () (values 1 2 3 4))

(defun foo ()
  (declare (special x y))
  (list x y $z $w))     ; Look Ma, no warnings!

(setf x nil y nil z nil w nil)

; Sample output:
? (foo)
(NIL NIL NIL NIL)
? (bind x = 1 in (list x (foo)))
(1 (NIL NIL NIL NIL))
? (bind $x = 1 in (list x (foo)))
(1 (1 NIL NIL NIL))
? (bind $x = 1 x = 2 in (list x (foo)))
(2 (1 NIL NIL NIL))
? (bind (x $y z $w) '(1 2 3 4) in (list x y z w (foo))) ; destrucuring-bind
(1 2 3 4 (NIL 2 NIL 4))
? (bind (values x $y z $w) (baz) in (list x y z w (foo))) ; multiple-value-bind
(1 2 3 4 (NIL 2 NIL 4))
? 
|#

From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3160870773012596@naggum.no>
* Erann Gat
| *You* might not have DEFVARed X, but how do you know that Joe didn't?

  it seems to me that this the fundamental question.  the answer lies in
  the implementation's excellence in implementing the function `describe'
  and any other environment-querying functions.

  however, there _is_ something we can and should do: add explicit support
  for retrieving this important piece of information about a symbol, apart
  from the rather obvious user interface issues like querying the system
  when at a symbol name in Emacs.  the compiler and the interpreter could
  also be asked to produce warnings about special variables for those who
  need them.  (I'd favor declaring variables special locally as a nice way
  to document the known special effects and also silence such warnings.)

  removing special variables because they confuse a few people is a typical
  "modern" reaction to the lack of diligence and effort that "modern" users
  are no longer expected to expend in learning anything.  this is simply a
  beginner's issue.  Common Lisp used to cater to experienced programmers
  at the cost of having to learn it, like a _skill_, something people of
  reasonable competence levels would _value_.  such is of course terribly
  politically incorrect in this day and age, where blathering idiots get to
  vote as many times as they can by virtue of forgetting the question and
  anyone with any experience at all is considered prejudiced by virtue of
  not answering all questions up for vote with a blank stare.

  I vote that Common Lisp remain a language that needs to be learned and
  studied, and instead focus our attention on stuff that actually affects
  users of all categories much more than this trifling issue, like being
  compatible with the notion in languages with which we would like to
  communicate of what constitutes a symbol name: the actual, literal
  sequence of characters (dollar signs included), not some case-mangled
  version of same.

  I also vote that somebody write "the complete idiot's guide to special
  variables" instead of proposing silly language changes.

| $x == (symbol-value 'x)

  I think "Common Perl" would be a good name for your modified language,
  with syntax in macros and equal signs and all.  yuck.

#:Erik
From: Janos Blazi
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38bcbaae_2@goliath.newsfeeds.com>
As changing the language is a long term project at best, it really would be
helpful if somebody wrote a guide mentioned in another response (though I
should choose a different title :) .)
I must admit that I for example do not understand these things well. Now it
is easy to expect others to do something for you but on the other hand this
should have to be done by someone who is an expert. And it should be written
in a simple language (as simple as possible) with all terms carefully
defined and with a *lot* of examples.

Janos Blazi


Erann Gat <···@jpl.nasa.gov> schrieb in im Newsbeitrag:
····················@milo.jpl.nasa.gov...
>
> I've been watching the recent threads on special variables, top-level
> setq-s and the like, and I've come to the conclusion that the current
> situation is badly broken.  I have a proposal on how to fix it that I'd
> like some feedback on.
>
> The intractable problem is that beginners are chronically confused by
> the fact that Lisp does not make an adequate syntactic distinction
> between two completely different ways of binding variables.  Imagine
> you are reading some code and you encounter the following two functions:
>
> (defun foo (x) (blarg x))
>
> (defun baz (y) (blarg y))
>
> Do FOO and BAZ do the same thing?  Well, they might or they might not.
> It depends.  It depends on whether X or Y have been DEFVARed.  It depends
> on whether there are any free references to X or Y in any function called
> by BLARG.  It depends on whether you are trying to write thread-safe code.
> It depends on whether performance differences matter.  It depends on
whether
> your code is interpreted or compiled.  And if you want to explain the
> reasons it depends on all these things you have to start talking about
> the differences between symbols and variables, what bindings are, and
> that there's nothing at all special about "special" variables, it's just
> an ancient piece of Lisp terminological baggage that means nothing more
> than "dynamic scope."
>
> A beginner's initiation into this state of affairs invariably comes when
> he or she one day as an expedient types (defvar x 1) and then spends the
> rest of the day (or week) trying to figure out why her code is suddenly
> exhibiting mysterious bugs.  The admonition to always use *...* notation
> for DAFVARed variables is a temporary fix, but it generally takes a very
> long time for a typical programmer to wrap their brains around what is
> really going on.
>
> The problem is pervasive and subtle.  Consider:
>
> (funcall (lambda (x y) (lambda () ... x ... y ...)) 1 2)
>
> Does this return a lexical closure over X and Y?  Well, it might, or it
> might not.  It depends.
>
> Now, this has not been much of an issue because artificially separating
> the name spaces of lexical and dynamic variables using the *...*
convention
> generally works to keep the problem at bay.  But the trouble is that this
> solution only works if you use it, and you can only use it if you are
> aware of it.  And even if you are aware of it, your collaborator might
> not be.  *You* might not have DEFVARed X, but how do you know that Joe
> didn't?
>
> The solution to this problem is to change the language so that the
> distinction between dynamic and lexical bindings is locally manifested.
> This is technically simple, but politically complex because it means
> either adding some kind of lexical declaration or getting rid of pervasive
> SPECIAL declarations (e.g. getting rid of DEFVAR, (PROCLAIM (SPECIAL ...))
> etc.)  My personal preference is the latter.  Top-level declarations that
> radically change the semantics of code in ways that are not lexically
> apparent are EVIL!
>
> Even local special declarations are IMO evil.  The semantics of a piece
> of code ought not to depend on forward references.  It's also very much
> against the spirit of a declaration.  Declarations are for providing extra
> information for the compiler.  They are not for changing the semantics of
> the program.  It should be possible to remove all declarations without
> changing anything about the program except how fast it runs.
>
> The solution is obvious.  Special variables are nothing more than the
> symbol-value slot of some symbol.  Why not make that simple fact manifest
> itself in the syntax?  For example:
>
> (let ( (x 1)                   ; A lexical binding
>        ((symbol-value x) 2) )  ; A dynamic binding
>
> While we're at it we could fold in the binding of multiple values and
> destructing into one uniform syntax:
>
> (superlet ( (x 1)                   ; A lexical binding (guaranteed)
>             ((symbol-value x) 2)    ; == (let ((x 2)) (declare (special
x))
>             ((values a b c) (foo))  ; == (multiple-value-bind (a b c)
(foo)
>             ((values a (symbol-value b) c) (baz))
>                                     ; As above, but with (declare (special
b))
>             ((a b c) (foo)) )       ; A DESTRUCTING-BIND
>
> A simple reader macro helps make things a lot less wordy:
>
> $x == (symbol-value 'x)
>
> So now we can write:
>
> (let ( (x 1) ($y 2) ) ; X is a lexical binding, Y is a dynamic binding
>
> This would work at top-level too:
>
> (setf $x 1) ; Set the global X with no warnings and no semantic ambiguity
> (setf x 1) --> Warning! No lexical variable named X visible here.  Setting
> $X instead.
>
> To implement this proposal completely requires the cooperation of Lisp
> implementors because you have to change the way lambda lists are
> processed.  But once that's done you can write (lambda (x $y) ...)
> instead of (lambda (x y) (declare (special y)) ...), or
> (multiple-value-bind (x $y) (foo) ...) instead of (multiple-value-bind
> (x y) (foo) (declare (special y)) ...) or (defun foo (x $y) ...) instead
> of (defun foo (x y) (declare (special y))  ...)
>
> As a prototype I have implemented a macro called BIND that works as
> described above.  BIND binds lexical and dynamic variables, and handles
> multiple values and destructuring.  It also uses a paren-less LOOP-like
> syntax.  I present it as both an illustration of how simple my proposal
> would be to implement properly, and as an illustration of how easy it is
> to change Lisp completely within the standard.
>
> The syntax for BIND is:
>
> (BIND var [=] value [and] ... in &rest body)
>
> var : symbol | (symbol-value symbol) | (values var var ...) | list
>
> Keywords in square brackets are optional.
>
> Example: (BIND x = 1 and (z ($y) q) = (foo) and (values $a b c) = (baz) in
...)
>
> expands to:
>
> (let ( (x 1) )
>   (destructuring-bind (z (y) q) (foo)
>     (declare (special y))
>     (multiple-value-bind (a b c) (baz)
>        (declare (special a))
>        ...
>
> I conjecture that beginners at least will find BIND easier to deal with
> than the things it replaces.
>
> Erann Gat
> ···@jpl.nasa.gov
> ---
>
>
> (set-macro-character #\$
>                      (lambda (s c)
>                        (declare (ignore c))
>                        (if (whitespacep (peek-char nil s))
>                          '|$|
>                          `(%symval ,(read s))))
>                      t)
>
> (defmacro %symval (x) `(symbol-value ',x))
>
> (defun process-vartree (vl)
>   (let ( (specials '()) )
>     (setf vl
>           (iterate loop1 ( (v vl) )
>             (cond ( (atom v) v )
>                   ( (eq (car v) '%symval)
>                     (push (second v) specials)
>                     (second v) )
>                   (t (cons (loop1 (car v)) (loop1 (cdr v)))))))
>     (values vl specials)))
>
> (defmacro bind (&rest forms)
>   (cond ( (null forms) (error "Missing IN keyword") )
>         ( (eq (car forms) 'in)
>           `(progn ,@(cdr forms)) )
>         ( (eq (car forms) 'and)
>           `(bind ,@(cdr forms)) )
>         (t (let ( (var (pop forms))
>                   (val (pop forms)) )
>              (if (eq val '=) (setf val (pop forms)))
>              (cond
>               ( (atom var)
>                 `(let ( (,var ,val) ) (bind ,@forms)) )
>               ( (eq (car var) '%symval)
>                 (setf var (second var))
>                 `(let ( (,var ,val) )
>                    (declare (special ,var))
>                    (bind ,@forms)) )
>               ( (eq (car var) 'values)
>                 (receive (vars specials) (process-vartree (cdr var))
>                   `(multiple-value-bind ,vars ,val
>                      (declare (special ,@specials))
>                      (bind ,@forms))) )
>               (t (receive (vars specials) (process-vartree var)
>                    `(destructuring-bind ,vars ,val
>                       (declare (special ,@specials))
>                       (bind ,@forms)))))))))
>
> #|
> ; Example:
> (defun baz () (values 1 2 3 4))
>
> (defun foo ()
>   (declare (special x y))
>   (list x y $z $w))     ; Look Ma, no warnings!
>
> (setf x nil y nil z nil w nil)
>
> ; Sample output:
> ? (foo)
> (NIL NIL NIL NIL)
> ? (bind x = 1 in (list x (foo)))
> (1 (NIL NIL NIL NIL))
> ? (bind $x = 1 in (list x (foo)))
> (1 (1 NIL NIL NIL))
> ? (bind $x = 1 x = 2 in (list x (foo)))
> (2 (1 NIL NIL NIL))
> ? (bind (x $y z $w) '(1 2 3 4) in (list x y z w (foo))) ;
destrucuring-bind
> (1 2 3 4 (NIL 2 NIL 4))
> ? (bind (values x $y z $w) (baz) in (list x y z w (foo))) ;
multiple-value-bind
> (1 2 3 4 (NIL 2 NIL 4))
> ?
> |#




-----= Posted via Newsfeeds.Com, Uncensored Usenet News =-----
http://www.newsfeeds.com - The #1 Newsgroup Service in the World!
-----==  Over 80,000 Newsgroups - 16 Different Servers! =-----
From: Keke Abe
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <keke-0103001606370001@tc-1-066.osaka.gol.ne.jp>
In article <····················@milo.jpl.nasa.gov>, ···@jpl.nasa.gov (Erann Gat) wrote:

> The problem is pervasive and subtle.  Consider:
> 
> (funcall (lambda (x y) (lambda () ... x ... y ...)) 1 2)
>
> Does this return a lexical closure over X and Y?  Well, it might, or it
> might not.  It depends.

It depends... but have you ever worried about x minght be special when
you write the code like above? The chance are so remote that I think
trying to eliminate it (by changing CL) is overkill.

> 
> Now, this has not been much of an issue because artificially separating
> the name spaces of lexical and dynamic variables using the *...* convention
> generally works to keep the problem at bay.  But the trouble is that this
> solution only works if you use it, and you can only use it if you are
> aware of it.  And even if you are aware of it, your collaborator might
> not be.

You can't force anyone not to write bad code by language spec alone.
(In this case, however, you can search DEFVAR form in the code?)

**

I don't think this is not a CL specific problem. And programmers
have already been advised to avoid the usage of 'global' variables
with indefinite scope unless it is necessary.

Is there anything particularly dangerous when a beginner equates
CL's special variables to global vars in other languages?


regards,
abe
From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3160886469599216@naggum.no>
* Keke Abe
| Is there anything particularly dangerous when a beginner equates
| CL's special variables to global vars in other languages?

  I can't answer for Erann, but my take on this is that beginners who get
  confused about this will remain confused for a few days, and then get it
  or get over it, as in: not worrying about it even if they don't get it.

  if we change the semantics of the language from what said confused people
  will find described in textbooks and other reference materials and when
  searching the net, the number of days of confusion can only increase, not
  the least because half the vendors will think this is a lame idea and not
  implement it, and the other half will do it better than the lame code and
  so the only thing we will succeed in is in destroying a very powerful
  mechanism in Common Lisp that every other language is sadly lacking:
  transparent, safe, and convenient global, dynamic variables.  all for the
  purported, but obviously unrealizable benefit of reducing the number of
  confused people and their posting frequency to comp.lang.lisp.

  still, it would be nice if we had some simple programmatic access to the
  specialness of a symbol.  this would have been covered by the environment
  access functions that were not included in the standard.

#:Erik
From: William Deakin
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38BCE870.C63A5CBB@pindar.com>
Erik wrote:

> ...but my take on this is that beginners who get confused about this will
> remain confused for a few days, and then get it or get over it, as in: not
> worrying about it even if they don't get it.

As a beginner, this is my experience. I'm in the not worrying about it (or is
that denial ;) stage. I found that this is one of those things that when I read
the description of special vs dynamic vs local caused my head to hurt, but in
practice has caused me little pain [1].

[...elided excellent reasons for not changing the sematics of the language...]

>   still, it would be nice if we had some simple programmatic access to the
>   specialness of a symbol.  this would have been covered by the environment
>   access functions that were not included in the standard.

This IMHO is a good idea.

Best Regards,

:) will

[1] Except in the case when I was writing some macros with cmucl. But this
maybe more of an issue with the implementation declaring all top level
variables special. More and better descriptions of this are elsewhere.
From: Sam Steingold
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <un1oizojs.fsf@ksp.com>
>>>> In message <················@naggum.no>
>>>> On the subject of "Re: A modest proposal (long)"
>>>> Sent on 01 Mar 2000 08:01:09 +0000
>>>> Honorable Erik Naggum <····@naggum.no> writes:
 >> 
 >>   still, it would be nice if we had some simple programmatic access
 >>   to the specialness of a symbol.  

in CLISP:
(defvar x)
(system::special-variable-p 'x) ==> T

-- 
Sam Steingold (http://www.podval.org/~sds)
Micros**t is not the answer.  Micros**t is a question, and the answer is Linux,
(http://www.linux.org) the choice of the GNU (http://www.gnu.org) generation.
My other CAR is a CDR.
From: ·······@my-deja.com
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <89jv80$6p9$1@nnrp1.deja.com>
In article <················@naggum.no>,
  Erik Naggum <····@naggum.no> wrote:
> * Keke Abe
> | Is there anything particularly dangerous when a beginner equates
> | CL's special variables to global vars in other languages?
>
> I can't answer for Erann, but my take on this is that
> beginners who get confused about this will remain confused for
> a few days, and then get it or get over it, as in: not worrying
> about it even if they don't get it.

It's not just a beginner problem. The program
  (DEFUN FOO (X) (BAR X))
  (DEFVAR X)
means something different from
  (DEFVAR X)
  (DEFUN FOO (X) (BAR X))
And if the DEFVAR is in one file, and the DEFUN is in another,
then the semantics change silently depending on what order
you compile them in. You wrote

> transparent, safe, and convenient global, dynamic variables

but I'd say this is a design flaw that makes them not particularly
safe.

I don't think it's a bad enough problem to justify changing the
language to solve it, but it's a real problem, even for real,
experienced programmers. I recently finished renaming
most of the special variables in the SBCL implementation of
Common Lisp to use the *FOO* convention. It was a considerable
amount of work. And even for the variables which use this convention,
I still have to worry about subtly breaking something a la
  (DEFVAR *FOO*)
  (DEFUN BAR (..)
    (LET ((*FOO* (..)))
       (BLETCH *FOO*)
       (ZUT)
  ;; Don't move the DEFVAR to here, or you will lose.
  (DEFUN ZUT () ; which I hope isn't something obscene in Italian:-)
    (IF *FOO* (ZUT1) (ZUT2)))
when *FOO*, BAR, and ZUT are defined in different files and
the order of compilation might be rearranged. I'd need to be
fairly unlucky to rearrange just the right things in just the right
way to silently break something like this, but it could happen.

By and large, Common Lisp does a good job of letting you define things
in any order, which is a good thing. By and large, when you can't
define things in any order (e.g. DEFCLASS) at least it gives you
an error, which is a good thing. But the problem I described just
above won't give you an error in any implementation I'm aware of,
which is nasty.

(By the way, I've considered making SBCL issue STYLE-WARNINGs
for any SPECIAL use of non-*FOO*-style symbols, and any non-SPECIAL
use of *FOO*-style symbols, to detect problems like this. But I'm
a little uncomfortable embedding informal naming conventions in the
compiler, so I've avoided doing this so far. Does anyone have
any opinions on whether such STYLE-WARNINGs would be The Right
Thing?)

> still, it would be nice if we had some simple programmatic
> access to the specialness of a symbol.  this would have been
> covered by the environment access functions that were not
> included in the standard.

Yes, I also really wish there was a standard way to
query "is symbol FOO special?" And "what's the value of the
optimization property BAR?" too..

  Bill Newman


Sent via Deja.com http://www.deja.com/
Before you buy.
From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3160943130779380@naggum.no>
* Bill Newman
| It's not just a beginner problem. The program
|   (DEFUN FOO (X) (BAR X))
|   (DEFVAR X)
| means something different from
|   (DEFVAR X)
|   (DEFUN FOO (X) (BAR X))
| And if the DEFVAR is in one file, and the DEFUN is in another, then the
| semantics change silently depending on what order you compile them in.

  I maintain that this is a beginner problem, only.  real Lisp programmers
  don't call their global variables "X".  real Lisp programmers use
  packages if they want their symbols to stay of other people's face.  real
  Lisp programmers know about unintern, too.

| I'd say this is a design flaw that makes them not particularly safe.

  it's a design flaw to you because your notion of safe is wrong.

| (By the way, I've considered making SBCL issue STYLE-WARNINGs for any
| SPECIAL use of non-*FOO*-style symbols, and any non-SPECIAL use of
| *FOO*-style symbols, to detect problems like this. But I'm a little
| uncomfortable embedding informal naming conventions in the compiler, so
| I've avoided doing this so far. Does anyone have any opinions on whether
| such STYLE-WARNINGs would be The Right Thing?)

  I have already said what I think is the right thing here: demand that
  there be lexically apparent declarations that reiterate the special
  status of symbols so declared globally.  lacking such a declaration, you
  might issue a style-warning for free variables even if you know they are
  globally declared special.  it will lead to slightly more verbose code,
  but the excuse to be making invisible, pervasive changes would go away.

| Yes, I also really wish there was a standard way to query "is symbol FOO
| special?" And "what's the value of the optimization property BAR?" too..

  precisely, and this is the _only_ problem worth solving as I see it.

#:Erik
From: ·······@my-deja.com
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <89kh6d$k1o$1@nnrp1.deja.com>
In article <················@naggum.no>,
  Erik Naggum <····@naggum.no> wrote:
> * Bill Newman
> | It's not just a beginner problem. The program
> |   (DEFUN FOO (X) (BAR X))
> |   (DEFVAR X)
> | means something different from
> |   (DEFVAR X)
> |   (DEFUN FOO (X) (BAR X))
> | And if the DEFVAR is in one file, and the DEFUN is in another, then
the
> | semantics change silently depending on what order you compile them
in.
>
>   I maintain that this is a beginner problem, only.  real Lisp
> programmers don't call their global variables "X".  real Lisp
> programmers use packages if they want their symbols to stay
> of other people's face.  real Lisp programmers know about
> unintern, too.

I don't think I'm going to be able to convince you of matters of taste
here. (I've never seen anyone else do it.:-) But perhaps I can at
least illustrate that there are more things in heaven and earth than
are dreamt of in your philosophy. (Or, in software engineering as
in quantum mechanics, the universe is not only stranger than we imagine,
it is stranger than we can imagine.)

The programmers who wrote the Python compiler (part of CMU CL,
available at http://www.cons.org/cmucl/) weren't beginners. But
they put somewhat over 10K lines of Common Lisp into the "C"
package (the compiler). And they defined special variables with
names like
      C::TOP-LEVEL-LAMBDA-MAX
      C::NO-LOADS
      C::PACK-OPTIMIZE-SAVES
      C::PACK-SAVE-ONCE
      C::MAX-OPTIMIZE-ITERATIONS
      C::PACK-ASSIGN-COSTS
      C::VM-SUPPORT-ROUTINES
      C::PRIMITIVE-TYPE-SLOT-ALIST
      C::NO-COSTS
      C::SYSTEM-CONSTANTS
I'm not trying to claim this was good style, or a good idea. (As I
said in my earlier article, I've since renamed as many special
variables as possible in the *FOO* style.) All I'm trying to claim is
that this example shows that the problem is not confined to beginners.
It was created by experienced programmers, and it bites experienced
programmers now who have to worry about not naming local variables
NO-LOADS. And even now that the special variables have been renamed
in the *FOO* style in my version (SBCL), I still need to worry about
respecting constraints on the order of compilation of code, with
no help from the compiler even to tell me when something goes wrong.

Incidentally, experienced C and C++ programmers can avoid many of the
problems of C and C++, such as
   * using the preprocessor to define constants
   * having to manually free memory resources
   * having wild pointers be able to corrupt the system
But that because these problems mostly trouble beginners (or maintainers
of large programs written by others) doesn't mean that these problems
aren't shortcomings of C and C++. Why should the fact that the special
variable problem mostly troubles beginners (or maintainers of large
programs written by others) mean that this problem isn't a shortcoming
of Common Lisp?

  Bill Newman


Sent via Deja.com http://www.deja.com/
Before you buy.
From: Tim Bradshaw
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <ey3u2iqgkix.fsf@cley.com>
* wnewman  wrote:
> Incidentally, experienced C and C++ programmers can avoid many of the
> problems of C and C++, such as
>    * using the preprocessor to define constants
>    * having to manually free memory resources
>    * having wild pointers be able to corrupt the system


Most of the experienced C and C++ programmers I know spend most of
their time avoiding the latter two and/or buy very expensive tools
(purify) to help them.  Most of them are *very* troubled by these
issues!

There's a real difference between problems which just go away, and
problems that you eventually realise you can live with, but will just
cost you 30% of your time for ever.

The CMUCL thing is a fine example of the former.  Whoever did that was
being silly, and there's a once off fix involving DO-SYMBOLS and
tags-query-replace in emacs which really should not take that long.

--tim
From: ·······@my-deja.com
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <89lv8q$jem$1@nnrp1.deja.com>
In article <···············@cley.com>,
  Tim Bradshaw <···@cley.com> wrote:
> * wnewman  wrote:
> > Incidentally, experienced C and C++ programmers can avoid many of
the
> > problems of C and C++, such as
> >    * using the preprocessor to define constants
> >    * having to manually free memory resources
> >    * having wild pointers be able to corrupt the system
>
> Most of the experienced C and C++ programmers I know spend most of
> their time avoiding the latter two and/or buy very expensive tools
> (purify) to help them.  Most of them are *very* troubled by these
> issues!
>
> There's a real difference between problems which just go away, and
> problems that you eventually realise you can live with, but will just
> cost you 30% of your time for ever.

Yes, I am not trying to argue that the special variable thing is a big
problem; certainly not one on the scale of the big C problems. But I
thought Erik was off base to say that because experienced programmers
know how to avoid it it's a non-problem. I think it's like the
preprocessor problems, or the confusion of C declarator syntax, a
price which is worth paying for a useful and stable language, but
IMHO unquestionably a flaw in the language.

Incidentally, while looking back through my development log for
the string "special variable" to find the symbol names, I noticed
that I'd actually logged a case where this had caused problems
for me. Fortunately they were gross problems (raising an error
because of an unbound variable) instead of subtle problems of
silently computing the wrong answer.

  PROBLEM:
      Assembling assembly/x86/assem-rtns.lisp fails with
	RETURN-MULTIPLE assembled
	TAIL-CALL-VARIABLE assembled
	THROW assembled
	UNWIND assembled
	Error in KERNEL::UNBOUND-SYMBOL-ERROR-HANDLER:
	  the variable %C::*FIXUPS* is unbound.
  MUSING:
      Searching for all references to *FIXUPS* shows
    that it is bound in ASSEMBLE-FILE and GENERATE-CODE.
      BACKTRACE from the error shows
  0: ("DEFUN NOTE-FIXUP" #<unused-arg> 187)
  1: (%ASSEM::FILL-IN #<Closure Over Function "DEFUN NOTE-FIXUP"
{480FA399}> 0)
  2: (%ASSEM::PROCESS-BACK-PATCHES #<%ASSEM:SEGMENT :NAME "Regular">)
  3: (%ASSEM:FINALIZE-SEGMENT #<%ASSEM:SEGMENT :NAME "Regular">)
  4: (%C:ASSEMBLE-FILE "src/assembly/target/assem-rtns.lisp"
                     :OUTPUT-FILE
  "obj/from-xc/assembly/target/assem-rtns.lisp-obj-tmp"
                     :TRACE-FILE
                     ...)
  5: (COMPILE-STEM "assembly/target/assem-rtns" :OBJ-PREFIX
"obj/from-xc/" :OBJ-SUFFIX ...)
  6: (IN-TARGET-CROSS-COMPILATION-MODE
    #<Closure Over Function "LAMBDA (STEM &KEY ASSEM-P
IGNORE-FAILURE-P)" {48005A41}>)
  7: ("Top-Level Form")[:TOP-LEVEL]
      So why the heck isn't *FIXUPS* bound, then?
      I tried to look at the problem more closely using
    /SHOW statements, and it went away. I guess it went
    away simply because I recompiled and/or reloaded
    assemfile (with HOST-CLOAD-STEM). I tested whether
    rebuilding assemfile with TARGET-COMPILE-STEM would
    cause the problem to return, and it didn't. This
    is weird..
      Oh! *FIXUPS* is only declared special by
    DEFVAR *FIXUPS* in compiler/fixup.lisp, and in my
    stems-and-flags.lisp-expr build sequence,
    assembly/assemfile is compiled before compiler/fixup.
    CMUCL doesn't notice this problem because *FIXUPS*
    is used in a function call which is lexically inside
    ASSEMBLE-FILE: its only mechanism for raising a
    warning related to this is when the undeclared
    special variable isn't used within the lexical body
    at all. So the compilation silently had different
    semantics when done in the ordinary build process
    and when done later interactively, after *FIXUPS*
    had been declared special. And no warnings or
    errors were raised along the way. (Common Lisp's
    special variable system really is somewhat dain-bramaged..)
  FIX:
    * Declare %C::*FIXUPS* special in early-c.lisp, 'way early
      in the build sequence.

Perhaps the bewildered tone of my notes to myself at the time
show that I was not (and perhaps never will be:-) an Erik-level
real programmer, but I am at least a programmer in the real world,
and I was actually bitten by this problem.

> The CMUCL thing is a fine example of the former.  Whoever did that was
> being silly, and there's a once off fix involving DO-SYMBOLS and
> tags-query-replace in emacs which really should not take that long.

Yes, it was silly. And yes, I fixed it exactly this way, although it
turned out to be sufficiently tedious that for one particularly
prolific family of misnamed specials I just gave up. From my log again:

  * The FOO-TN-named variables created by
    the DEF-MISC-REG-TNS macro are too numerous and used
    too widely for it to be reasonable to rename them
    to *FOO-TN*. For now I'll leave them alone, with a
    FIXME note wishing they were constants.

  Bill Newman


Sent via Deja.com http://www.deja.com/
Before you buy.
From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3160951975373812@naggum.no>
* ·······@my-deja.com
| All I'm trying to claim is that this example shows that the problem is
| not confined to beginners.

  but your example doesn't show any such thing!  that people are not
  following the asterisk convention is _not_ the problem.  the problem as
  stated is that there's a lambda list or let binding somewhere with a
  symbol in it that has special binding which comes as a _surprise_ to
  people who are moderately (but not overly) intimate with the code.  do
  you have evidence of that, or is this only more unfounded fear that there
  _might_ be a problem?  incidentally, I recognize that there _might_ be a
  problem, the solution to which is to make the system easier to query for
  such information.  I don't see any other problems that need solving.

  my philosophy, in case you need to have it stated to avoid speculating
  about it, is that in order to serve the needs of any community, one must
  never, _ever_ to cater to the needs of ignorants and novices except in
  carefully controlled settings where the express purpose is to make them
  non-ignorants and non-novices, such as school or training courses.

#:Erik
From: Marc Battyani
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <45385439B946F46E.1E78BE0D29FB332C.7704F294A03119BE@lp.airnews.net>
<·······@my-deja.com> wrote in message ·················@nnrp1.deja.com...
> (By the way, I've considered making SBCL issue STYLE-WARNINGs
> for any SPECIAL use of non-*FOO*-style symbols, and any non-SPECIAL
> use of *FOO*-style symbols, to detect problems like this. But I'm
> a little uncomfortable embedding informal naming conventions in the
> compiler, so I've avoided doing this so far. Does anyone have
> any opinions on whether such STYLE-WARNINGs would be The Right
> Thing?)

It seems to be already the case in LispWorks:

META-LEVEL 4 > (let ((var nil)))
nil

META-LEVEL 5 > (let ((*var* nil)))
Warning: Syntactic warning for form (let ((*var* nil))):
   *var* bound lexically.
nil

I just noticed this today because I got one after having changed the load
order of some files.
Saved my day!

So yes such warning are useful.

Marc Battyani
From: Tim Bradshaw
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <ey3ln42j056.fsf@cley.com>
I think I agree with Erik about this.  There is clearly a problem here
in principle.  In practice I have *very* seldom been bitten by it, and
I'd be loth to change the language to make it `easier' for people at
the cost of adding something like the BIND macro you suggest (at
least, not with the syntax you suggest, which I have much the same
reaction to as Erik I'm afraid).  I'm also very loth to use up one of
the extremely small number of available characters to be a read-macro
for something like this.

I'd also like to gratuitously point out that your technique doesn't
actually solve the whole problem: symbol-macros can mean that what
looks like an innocent variable is actually something entirely
different.

I think a much more useful meta-solution to this problem is better
environmental information, and a compiler MOP and/or code walker.
Given that I can instrument the compiler in such a way that it will
warn me if it ever sees a special variable that does not adhere to
whatever naming convention I choose, or in general check any other
thing I like about the code I'm compiling.

And this solution has the advantage that it's useful for other stuff
too!

--tim
From: Robert Posey
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38BD561C.39C06B80@raytheon.com>
Tim Bradshaw wrote:
> 
> I think I agree with Erik about this.  There is clearly a problem here
> in principle.  In practice I have *very* seldom been bitten by it, and
> I'd be loth to change the language to make it `easier' for people at
> the cost of adding something like the BIND macro you suggest (at
> least, not with the syntax you suggest, which I have much the same
> reaction to as Erik I'm afraid).  I'm also very loth to use up one of
> the extremely small number of available characters to be a read-macro
> for something like this.

I have to conditionally agree with Erik (someone stop me, Please!!) if
their experience is representative of general programing experiences. 
Structure changes in well established languages should only be made based
as hard of data as possible.  Before you change a basic feature like this,
make sure the problem exists for programers or program teams who have
at least 2-3 months of real experience ( not classes, or individual projects).
For problems that mostly only effect beginners, more environmental 
information is both easier to implement and serves an educational
purpose.  I personnely(based on C, C++ and assembly lang exp) would 
find a describe function that would provide an complete description
of the scope and type of a variable at the CURRENT time to be more
useful.  It would also be very nice, if the development system
would list all of the variables visible at a given level.  While
I find *name* notation a little strange, hopefully there are not
too many development teams of any size that do not have enforced
naming standards for all variables and functions. 


BTW does anyone
know of a reference that has a GOOD description of hopefully
general methods to come up with a naming standard for symbols, 
variables, functions etc.?  Is there something approaching a standard.

My best coding experience was one in C, where the name of a variable or
function told you in what file it was define, whether it was global,
or a constant.  It didn't include type, but that wasn't too much of
a problem since almost every thing was an Integer, and on the
DSP we were using short, int, long integer were all 32 bits and
strings only existed in 2 out of 200 files.  

Muddy





> I think a much more useful meta-solution to this problem is better
> environmental information, and a compiler MOP and/or code walker.
> Given that I can instrument the compiler in such a way that it will
> warn me if it ever sees a special variable that does not adhere to
> whatever naming convention I choose, or in general check any other
> thing I like about the code I'm compiling.
> 
> And this solution has the advantage that it's useful for other stuff
> too!
> 
> --tim
From: Robert Monfera
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38BD5C88.40C52D5A@fisec.com>
Robert Posey wrote:

> My best coding experience was one in C, where the name of a variable
> or function told you in what file it was define[d]

It would astonish and maybe convert even the most avid advocates of
Hungarian coding.

Robert
From: Pierre R. Mai
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <87aekio8yj.fsf@orion.dent.isdn.cs.tu-berlin.de>
Robert Posey <·····@raytheon.com> writes:

> BTW does anyone
> know of a reference that has a GOOD description of hopefully
> general methods to come up with a naming standard for symbols, 
> variables, functions etc.?  Is there something approaching a standard.

I don't think there are general standards, apart from:

- Use * to surround global special variables
- Use + to surround global constants
- Let yourself be guided by the (newer parts of the) ANSI CL standard
  for ideas on how to name accessors, functions and variables.

> My best coding experience was one in C, where the name of a variable or
> function told you in what file it was define, whether it was global,
> or a constant.  It didn't include type, but that wasn't too much of
> a problem since almost every thing was an Integer, and on the
> DSP we were using short, int, long integer were all 32 bits and
> strings only existed in 2 out of 200 files.  

Well, since every useful (Lisp) development environment will include
functions to locate the corresponding definition, encoding filenames
in the names isn't very useful nowadays.  Since in CL objects are
typed and (normally) not variables, it doesn't make much sense to
include type information in the name either.

Regs, Pierre.

-- 
Pierre Mai <····@acm.org>         PGP and GPG keys at your nearest Keyserver
  "One smaller motivation which, in part, stems from altruism is Microsoft-
   bashing." [Microsoft memo, see http://www.opensource.org/halloween1.html]
From: Robert Posey
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38BD6F03.3B78432D@raytheon.com>
"Pierre R. Mai" wrote:
> 
> Robert Posey <·····@raytheon.com> writes:
> 
> 
> Well, since every useful (Lisp) development environment will include
> functions to locate the corresponding definition, encoding filenames
> in the names isn't very useful nowadays.  Since in CL objects are
> typed and (normally) not variables, it doesn't make much sense to
> include type information in the name either.

That's if you are reviewing the code using the development system, that
is often not the case where I work, or I suspect on many large development
teams.

Muddy

> 
> Regs, Pierre.
> 
> --
> Pierre Mai <····@acm.org>         PGP and GPG keys at your nearest Keyserver
>   "One smaller motivation which, in part, stems from altruism is Microsoft-
>    bashing." [Microsoft memo, see http://www.opensource.org/halloween1.html]
From: Pierre R. Mai
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <87d7pecw9z.fsf@orion.dent.isdn.cs.tu-berlin.de>
Robert Posey <·····@raytheon.com> writes:

> > Well, since every useful (Lisp) development environment will include
> > functions to locate the corresponding definition, encoding filenames
> > in the names isn't very useful nowadays.  Since in CL objects are
> > typed and (normally) not variables, it doesn't make much sense to
> > include type information in the name either.
> 
> That's if you are reviewing the code using the development system, that
> is often not the case where I work, or I suspect on many large development
> teams.

How do you review the code? On printed paper?

Regs, Pierre.

-- 
Pierre Mai <····@acm.org>         PGP and GPG keys at your nearest Keyserver
  "One smaller motivation which, in part, stems from altruism is Microsoft-
   bashing." [Microsoft memo, see http://www.opensource.org/halloween1.html]
From: Robert Posey
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38BDADC2.2988546F@raytheon.com>
"Pierre R. Mai" wrote:
> 
> Robert Posey <·····@raytheon.com> writes:
> 
> > > Well, since every useful (Lisp) development environment will include
> > > functions to locate the corresponding definition, encoding filenames
> > > in the names isn't very useful nowadays.  Since in CL objects are
> > > typed and (normally) not variables, it doesn't make much sense to
> > > include type information in the name either.
> >
> > That's if you are reviewing the code using the development system, that
> > is often not the case where I work, or I suspect on many large development
> > teams.
> 
> How do you review the code? On printed paper?
Usually, its sent as a text file and I review it as a separate file on
a PC, in a code highlighting editor.  So there is no way for the system
to know data from other files.  This is partly a result of using Ada, and
old very limited tools.  Since we are switching to C/C++, hopefully we will
start using smart tools.  So I have zero experience reviewing other people's
code, using reasonable tools.  My LISP coding experience is so far simply
class work or playing around, and is pretty limited at the moment.  Another
problem is that many programs have classified code on them, which means that
some small part of the code is classified.  What I work on is not classified,
so I often have limited access.  They are starting to use Green hill compilers
and Vxworks so I hope they will support better collaboration, but I wouldn't
be surprised to see massive resistance to using an advanced features.  However,
I still think that you are going to run into problems if you don't use
structured
names, it seems so much easier to read the code that way.  Its a pain to always
have to click on every symbol to find out what it really means.  

Muddy
> 
> Regs, Pierre.
> 
> --
> Pierre Mai <····@acm.org>         PGP and GPG keys at your nearest Keyserver
>   "One smaller motivation which, in part, stems from altruism is Microsoft-
>    bashing." [Microsoft memo, see http://www.opensource.org/halloween1.html]
From: Pierre R. Mai
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <874sapd3k6.fsf@orion.dent.isdn.cs.tu-berlin.de>
Robert Posey <·····@raytheon.com> writes:

[ Reviewing code ]

> Usually, its sent as a text file and I review it as a separate file on
> a PC, in a code highlighting editor.  So there is no way for the system
> to know data from other files.  This is partly a result of using Ada, and

I wouldn't blame Ada itself for this.  There are Ada environments out
there, that integrate fairly well with "modern" tools.  But I know
what you mean:  There are also some fairly clunky Ada tool-chains out
there.

> old very limited tools.  Since we are switching to C/C++, hopefully we will
> start using smart tools.  So I have zero experience reviewing other people's

I wouldn't hang my hopes too high, though.  I think the usability of a
development environment corellates highly with the organization in
question, and less with the actual languages used, or the environments
available.

> code, using reasonable tools.  My LISP coding experience is so far
> simply class work or playing around, and is pretty limited at the
> moment.  Another problem is that many programs have classified code
> on them, which means that some small part of the code is classified.
> What I work on is not classified, so I often have limited access.

Yes, in classified environments, usability often suffers hideously.
Been there, done that, got the scars and no T-shirt. :)

> to see massive resistance to using an advanced features.  However, I
> still think that you are going to run into problems if you don't use
> structured names, it seems so much easier to read the code that way.

Oh, I didn't advocate not using structured names.  I mean all the
tool support in the world isn't going to help you when you've got
a mess of uncommunicative variable names floating around.

I just don't think that using filenames for structure is the right
approach.  The name of the file something is defined in only matters
when you want to open that file.  With a modern environment, you just
press M-. or M-, and the editor will pop up the definition of the
thing at point.  Together with the fact that files are just one way of 
organizing source code (many advanced environments are moving to
non-file based repositories -- which has it's advantages and
disadvantages), that makes files not very meaningful.

What I do advocate is naming files in a way that makes the logical
"location" of something apparent, so that you can see what something
means (and in a hitch, given useful filenaming conventions, you could
even find in manually).

For example naming functions like the following (this isn't a mechanical
matter, since you have to take non-related class hierarchies into account):

;;; Class with reader

(defclass http-message ()
  ((server :initarg :server :reader http-message-server
           :documentation "The server this message belongs to.")))

;;; Accessor

(defgeneric http-message-version (message)
  (:documentation "Returns the HTTP-Version of the given message."))

;;; "Action"

(defgeneric render-http-message (message stream)
  (:documentation "Render the given message on the stream."))

Accessors for attributes of objects get names like

logical-name-attribute

and actions on objects get names like

verb-logical-name(-prepositional-phrases)

Note that the logical-name in question is often but not always the
name of the top class for which this operation makes sense (i.e. which 
"introduces" this operation).  In cases where unrelated class
hierarchies define methods on the GF in question, a logical
name for the generalization must be found (see for example the object
in print-object, where ANSI CL has no class named object).

While it is more difficult to get people to use logical instead of
mechanical naming conventions consistently, I think it's worth the
effort.  With critical reviews of chosen names during code reviews,
and the discussions they'll cause, you will get a) fairly consistent
naming, and much more importantly b) a steadily re-established general
consensus on the important concepts of your project, their names,
meanings and implications.

> Its a pain to always have to click on every symbol to find out what
> it really means.

This shouldn't ever be necessary.  If you get to this stage, you're
generally lost.

Regs, Pierre.

-- 
Pierre Mai <····@acm.org>         PGP and GPG keys at your nearest Keyserver
  "One smaller motivation which, in part, stems from altruism is Microsoft-
   bashing." [Microsoft memo, see http://www.opensource.org/halloween1.html]
From: Erann Gat
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <gat-0103001158360001@milo.jpl.nasa.gov>
In article <···············@cley.com>, Tim Bradshaw <···@cley.com> wrote:

> I think I agree with Erik about this.  There is clearly a problem here
> in principle.  In practice I have *very* seldom been bitten by it, and
> I'd be loth to change the language to make it `easier' for people at
> the cost of adding something like the BIND macro you suggest (at
> least, not with the syntax you suggest, which I have much the same
> reaction to as Erik I'm afraid).  I'm also very loth to use up one of
> the extremely small number of available characters to be a read-macro
> for something like this.

I see I have not made myself clear.

The $ macro is optional.  So is the BIND macro.  The core of my
proposal is to move the specification of dynamic bindings out of
the declarations and into the lambda list.  It's a 100% backwards-
compatible change, and it doesn't change the semantics of the language
at all.  It's also very much in the spirit of Common Lisp.  All I am
saying is that we should extend lambda-list syntax to allow variables
whose names are lists beginning with SYMBOL-VALUE (or SPECIAL or
DYNAMIC, I don't really care which keyword we choose).  It's much
like extending the syntax of function names to include lists whose
first element is SETF.

BTW, all the keywords in the BIND macro are optional except IN, so you
can dispense with all the = signs and ANDs and just write:

(bind x 1 (symbol-value q) 2 (values y z) (foo) in ...)

It's also pretty simple to change BIND to use parens instead of a
keyword to separate the bindings from the body:

(bind (x 1 (symbol-value q) 2 (values x z) (foo)) ...)

or:

(bind ( (x 1)
        ((symbol-value q) 2)  ; implied (declare (special q))
        ((values y z) (foo))  ; multiple-value-bind
        ((a (symbol-value b) c) (baz)) )     ; destructuring (with a special)
  ...

Without BIND this code becomes:

(let ( (x 1)
       (q 2) )
  (declare (special q))
  (multple-value-bind (y z) (foo)
    (destructuring-bind (a b c) (baz)
       (declare (special b))

Personally, I think:

   (bind x 1 $q 2 (values y z) (foo) (a $b c) (baz) in ...

is a win.  Notice also that you can implement this without a reader macro.
BIND could simply declare special those variables whose print names start
with $, or whose print names start and end with *, thus:

  (bind ( (x 1) (*y* 2) ) ; *Y* is automatically declared special

We are already using a typographical convention to distinguish lexical and
special variables.  We already know that we get into trouble when we don't
adhere to that convention.  Why not move the burden of applying that
convention from the programmer to the compiler?

I also wonder how many of you BIND haters are also LOOP haters.  I am
really beginning to worry that people have lost sight of the fact that
an S-expression with just one level of parens is still an S-expression.

> I'd also like to gratuitously point out that your technique doesn't
> actually solve the whole problem: symbol-macros can mean that what
> looks like an innocent variable is actually something entirely
> different.

But symbol macros can only be established with lexical scope, so if
there is a symbol macro it must be lexically manifested.  Global symbol
macros would be truly problematic.  In fact, this is the problem with
DEFVAR.  It essentially establishes a global symbol macro that replaces
all occurrences of X with (symbol-value 'x), except that this happens
silently, and there's no way to undo it.

E.
From: Tim Bradshaw
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <ey3ya82gwgc.fsf@cley.com>
* Erann Gat wrote:

> I see I have not made myself clear.

No, I understood what you meant.  I just want to know if this is a
problem *in practice*[1], and if it is to think out a fix.  Common Lisp
is a pragmatic language and I don't think that changes to fix things
that aren't in practice an issue are needed.  That's why we don't have
hygienic macros, after all.

I also think that if you are going to make a change to the language
like this, you should think it out a good deal first.  For instance my
suggestion of better environmental access would enable you to detect
these kinds of problems yourself, but it would also enable a whole
bunch of other cool stuff.

If you want to stick to souping up lambda lists, why just fix this one
issue?  Why not let general declarations be in there? Step back from
the problem.

> The $ macro is optional.  So is the BIND macro.  The core of my
> proposal is to move the specification of dynamic bindings out of
> the declarations and into the lambda list.  It's a 100% backwards-
> compatible change, and it doesn't change the semantics of the language
> at all.  

But, if it becomes standard, it *does* make every current conforming
implementation non-conforming, and incurs a cost on every vendor who
wishes to remain conforming.  That is another reason to consider
changes really carefully, and, I think, another reason to make changes
that add as much value as possible rather than ad-hoc fixes to
individual perceived problems.

> But symbol macros can only be established with lexical scope, so if
> there is a symbol macro it must be lexically manifested.  Global symbol
> macros would be truly problematic.  In fact, this is the problem with
> DEFVAR.  It essentially establishes a global symbol macro that replaces
> all occurrences of X with (symbol-value 'x), except that this happens
> silently, and there's no way to undo it.

DEFINE-SYMBOL-MACRO establishes global symbol macros.  They are
shadowed by bindings however.

--tim

[1] All I can say is that, for me, this has not been a problem, and
people I've taught and worked with have not reported it as a problem.
But I can't speak for any very wide community.
From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3160942638240195@naggum.no>
* Erann Gat
| I see I have not made myself clear.

  I see no evidence of that.  I think we have a fairly good understanding
  of your issue.  all the silly syntax detracted from its delivery, but
  you've been clear enough.

| We are already using a typographical convention to distinguish lexical
| and special variables.  We already know that we get into trouble when we
| don't adhere to that convention.  Why not move the burden of applying
| that convention from the programmer to the compiler?

  because we would want to make our own conventions in code where it is
  safe to make them.  and people don't _actually_ get into trouble in the
  first place, except the first few days they are confused about this.

| I also wonder how many of you BIND haters are also LOOP haters.  I am
| really beginning to worry that people have lost sight of the fact that
| an S-expression with just one level of parens is still an S-expression.

  no need to worry about that.  I like loop, I don't if*, and I don't like
  your bind or any of the numerous other _gratuitous_ syntax-heavy ideas
  people seem to get with an alarming regularity whenever they see a need
  for some miniscule improvement to the language.  it's as if they don't
  like simple syntax to begin with, and rush to solve any semantic issue
  with syntax.  I find this disturbing, but nonetheless indicative of
  something much more important: the language changers don't really grok
  Common Lisp.

| But symbol macros can only be established with lexical scope, so if
| there is a symbol macro it must be lexically manifested.  Global symbol
| macros would be truly problematic.

  take a look at define-symbol-macro some day and weep, then.  I love the
  fact that we have global symbol macros!  I also love the fact that we
  have constants, which also causes pervasive differences in behavior, and
  there's no truly established convention for them.  I happen to think that
  special variables is one of Common Lisp's truly great idea.  what I want,
  in response to your "it's EVIL!" is a programmatic means to query the
  system for the status of a symbol.  `describe' and friends help me as a
  user who gawks at the screen, but that is clearly insufficient.

  again, there is a need to change the language to make it more amenable to
  beginners and experienced users alike: unlike all other languages now in
  current and widespread use, Common Lisp violates the notion that what you
  see is what you get with respect to the _names_ of the symbols.  if
  symbol-value is such a problem for beginners that it needs language-smith
  attention, wouldn't you be interested in solving a _real_ problem that
  would have far-reaching consequences for our interoperability with other
  languages, other textbooks, other people?  it's not a question of case,
  it's a matter of making (setf (readtable-case *readtable*) :preserve)
  work the way people _actually_ expect it to.  think about it.  please.

#:Erik
From: Erann Gat
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <gat-0103001927290001@milo.jpl.nasa.gov>
In article <················@naggum.no>, Erik Naggum <····@naggum.no> wrote:

> | But symbol macros can only be established with lexical scope, so if
> | there is a symbol macro it must be lexically manifested.  Global symbol
> | macros would be truly problematic.
> 
>   take a look at define-symbol-macro some day and weep, then.

You're right.  I overlooked define-symbol-macro.  I'm not weeping, but
I am shuddering.

>  I love the fact that we have global symbol macros!

What do you use them for?

>  I happen to think that
>   special variables is one of Common Lisp's truly great idea.

I agree.  The problem is not special variables.  The problem is the
way you tell Lisp which variables you want to make special and which
you don't.

>  what I want,
>   in response to your "it's EVIL!" is a programmatic means to query the
>   system for the status of a symbol.  `describe' and friends help me as a
>   user who gawks at the screen, but that is clearly insufficient.

The issue is not just one of querying.  It's also one of control.  There's
no way to undo the effects of a defvar short of uninterning the symbol.

>   again, there is a need to change the language to make it more amenable to
>   beginners and experienced users alike: unlike all other languages now in
>   current and widespread use, Common Lisp violates the notion that what you
>   see is what you get with respect to the _names_ of the symbols.

Maybe it would help to review the distinction between a variable and a
symbol (and the name of a symbol) just to make sure we are all on
the same page.  Variables, symbols, and names are all different.
For example, here we have three (lexical) variables, but only two
symbols, and only one name:

(lambda (x) (lambda (x) (lambda (foo::x) ...

(Actually, we have three variables ONLY if X has not been DEFVARed.
If X has been defvared then we only have two variables.)

When you bind a lexical variable you make a new variable.  When you
bind a special/dynamic variable you make a new binding for an existing
variable.

Specialness can be associated with variables (via SPECIAL declarations)
or with symbols (via DEFVAR) but NOT with names.  Once specialness has
been associated with a symbol, it is no longer possible to create new
variables using that symbol, only new bindings for the (one) special variable
associated with that symbol (also known as the symbol's symbol-value).

The point is that none of this has anything to do with symbol names.
In fact, you can make examples using symbols that don't even have names:

(defmacro weird-lambda (&body body)
  (let ( (arg1 (make-symbol ""))
         (arg2 (make-symbol "")) )
    `(lambda (,arg1 ,arg2) (declare (special ,arg1)) ...

Here there is one lexical binding and one dynamic binding.  They are
associated with two uninterned symbols, neither of which has a name!

Here's an even more pathological example:

(progn
  (defvar #1=#.(make-symbol "") 1)
  (defun #1# () #1#)
  (funcall (lambda (#1#) (#1#)) 2))

This wouldn't work in Scheme ;-)

>  if symbol-value is such a problem for beginners that it needs language-smith
>   attention, wouldn't you be interested in solving a _real_ problem that
>   would have far-reaching consequences for our interoperability with other
>   languages, other textbooks, other people?

I thought that's what I was doing, but it seems I still have not made
myself clear.  You seem to think that I am saying that the problem is
the existence of dynamic variables and symbol-value.  I'm not saying that
at all.  What I am saying is that the way things currently stand, when
you write 'X' you can't in general know whether what you've
written is a reference to a stack frame or a slot in an object on the heap.
And, in fact, as you yourself pointed out the meaning of X can change
over time if you are running interpreted. IMO that's bad.

>  it's not a question of case,
>   it's a matter of making (setf (readtable-case *readtable*) :preserve)
>   work the way people _actually_ expect it to.  think about it.  please.

It would help if you would stop talking in riddles.  I honestly have no
idea what you mean.

? (setf (readtable-case *readtable*) :preserve)
:PRESERVE
? 'foo
foo
? 'foO
foO
? 'FOO
FOO
? 

Works the way I'd expect it to.

E.
From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3160966858202840@naggum.no>
* Erann Gat
| The problem is not special variables.  The problem is the way you tell
| Lisp which variables you want to make special and which you don't.

  so let me disagree vociferously with that, too.  if we make necessary
  things inconvenient to express, it is not their expression that will
  suffer the most, but common recognition of their necessity.  the fact
  that special variables solve a problem that exist in _every_ programming
  language so conveniently, namely how to ascertain proper restoration of
  global variables, means that people aren't going to reinvent tricks with
  unwind-protect and the like (if they know about unwind-protect -- Kent
  Pitman has made the cogent argument that languages can be judged on the
  existence of such a language feature -- I'll argue that the same applies
  to programmers and whether they know about it).

  as soon as you start to make these special variables stand out as the
  wart on the language that you appear to believe they are, people will
  naturally avoid them (and the more so the more weirdo syntax soup you
  introduce, the threat of which I now realize is part of my objection to
  your syntax-heavy proposal), and choose the next best thing that looks
  like it could be sufficiently convenient.  then they start to make buggy
  or needlessly verbose code, which they'll loathe.  you're rocking the
  boat and making life miserable for those who _need_ special variables and
  need them _not_ to look _too_ special, because that destroys their very
  significant convenience factor.  I say: don't do that.  solve the actual
  problems, don't just push your special brand of cosmetics.

| The issue is not just one of querying.  It's also one of control.  There's
| no way to undo the effects of a defvar short of uninterning the symbol.

  so let's find a way to do that, instead, then.  (how hard can this be?)

  I think a Common Lisp environment needs universal functionality to "undo"
  or "kill" all definition forms.  Allegro CL has a nifty feature to kill
  various definitions from the Emacs interface, and I use it seldom enough
  to appreciate it very highly every time, but it does not accept defvar.
  (I'll file a request for enhancement for that.)  this might be considered
  annoying, but in the meantime, here's a couple tiny functions to muck
  with the gory internals of symbols in a way that is guaranteed to make a
  whole slew people want to puke violently, but if they get over it and
  realize that Common Lisp is all about _exporting_ an elegant interface to
  lots of really hairy stuff to begin with, they might actually rejoice and
  use these functions.

(in-package :excl)

#+allegro-v5.0.1
(defun symbol-special-p (symbol)
  (declare (optimize (speed 3) (safety 0)) (symbol symbol))
  (check-type symbol symbol)
  (if (and (not (eq nil symbol))
	   (zerop (ldb (byte 1 #.(system::mdparam 'compiler::md-symbol-flag-constant-bit))
		       (excl::sy_flags symbol))))
    (not (zerop (ldb (byte 1 #.(system::mdparam 'compiler::md-symbol-flag-globally-special-bit))
		     (excl::sy_flags symbol))))
    nil))

#+allegro-v5.0.1
(defun (setf symbol-special-p) (special symbol)
  (declare (optimize (speed 3) (safety 0)) (symbol symbol))
  (check-type symbol symbol)
  (if (and (not (eq nil symbol))
	   (zerop (ldb (byte 1 #.(system::mdparam 'compiler::md-symbol-flag-constant-bit))
		       (excl::sy_flags symbol))))
    (setf (excl::sy_flags symbol)
      (dpb (if special 1 0)
	   (byte 1 #.(system::mdparam 'compiler::md-symbol-flag-globally-special-bit))
	   (excl::sy_flags symbol)))
    (error "Cannot change special status of constant symbol ~S." symbol)))

  perhaps needless to say, you can hurt your Allegro CL system with the
  latter function, even though I have tried to restrict a few particular
  damages that users are likely to try (and I know how to restrict).

  if you don't have Allegro CL 5.0.1, this won't necessarily fail, but _you_
  had to remove the read-time conditionals so _you_ take the responsibility.

| >   again, there is a need to change the language to make it more amenable to
| >   beginners and experienced users alike: unlike all other languages now in
| >   current and widespread use, Common Lisp violates the notion that what you
| >   see is what you get with respect to the _names_ of the symbols.
| 
| Maybe it would help to review the distinction between a variable and a
| symbol (and the name of a symbol) just to make sure we are all on
| the same page.

  find, but sometimes, it isn't everybody else who need to be on your page.

| The point is that none of this has anything to do with symbol names.

  duh.  I'm trying to redirect your attention to a worth-while problem,
  entirely _away_ from messing with stuff you shouldn't be messing with.

| I thought that's what I was doing, but it seems I still have not made
| myself clear.   You seem to think that I am saying that the problem is
| the existence of dynamic variables and symbol-value.   I'm not saying
| that at all.   What I am saying is that the way things currently stand,
| when you write 'X' you can't in general know whether what you've written
| is a reference to a stack frame or a slot in an object on the heap.
| And, in fact, as you yourself pointed out the meaning of X can change
| over time if you are running interpreted.  IMO that's bad.

  and IMNSHO, it isn't bad at all.  I have pointed out that we need a few
  accessors into the environment to solve your uncertainty problem, and
  perhaps we need a `notspecial' or `lexical' declaration to be able to
  undo the pervasive effects of the `special' declaration.  however, I care
  so much about the language that I'm unwilling to consider your proposal
  when I understand the issues so much better than you do and I consider
  your proposal to be a major disturbance over a petty issue that mainly
  has to do with a disportional sense of uncertainty.  now, I fully
  recognize that uncertainty is one of those things that make people go
  nuts and that it is vitally important in a community to avoid swarms of
  neurotics who run around with proposals that are mainly intended to
  affect their mental state in some vaguely positive way, so I instead
  propose something that will make the uncertainty go away by adding a very
  low-level certainty instead of making any changes to superficial features
  that will take yet more forms as the swarm of neurotics has only been
  decimated for now, not actually cured of their unhealthy uncertainty.

| >  it's not a question of case,
| >   it's a matter of making (setf (readtable-case *readtable*) :preserve)
| >   work the way people _actually_ expect it to.  think about it.  please.
| 
| It would help if you would stop talking in riddles.

  geez.  there are no riddles.  I'm talking about something other than you
  do, because I think what you're talking about is counter-productive.  you
  missed that point entirely when you thought I was still talking about
  your concerns over specialness when I talked about symbol names.  I'm a
  little concerned with the breakdown of communication that occurs when
  people don't notice that others aren't talking about the same thing they
  are, anymore, but just keep on and on about whatever they had in mind.

| Works the way I'd expect it to.

  so try typing in (setf (readtable-case *readtable*) :upcase) and tell me
  what you expect to happen and/or that this is not a useful thing to do.
  (note again that this is no longer a question of special variables.)

#:Erik
From: Russell Wallace
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38BECBE4.37DA@iol.ie>
Erik Naggum wrote:
>   ...that people aren't going to reinvent tricks with
>   unwind-protect and the like (if they know about unwind-protect -- Kent
>   Pitman has made the cogent argument that languages can be judged on the
>   existence of such a language feature -- I'll argue that the same applies
>   to programmers and whether they know about it).

Can you give a reference to this, or summarize the argument in
question?  I must admit it wouldn't have occurred to me to pick that as
one of my primary criteria for judging languages (let alone
programmers), I'm curious as to the reasoning?

-- 
"To summarize the summary of the summary: people are a problem."
Russell Wallace
···············@iol.ie
From: Pierre R. Mai
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <87u2ipqb4k.fsf@orion.dent.isdn.cs.tu-berlin.de>
Russell Wallace <········@iol.ie> writes:

> Erik Naggum wrote:
> >   ...that people aren't going to reinvent tricks with
> >   unwind-protect and the like (if they know about unwind-protect -- Kent
> >   Pitman has made the cogent argument that languages can be judged on the
> >   existence of such a language feature -- I'll argue that the same applies
> >   to programmers and whether they know about it).
> 
> Can you give a reference to this, or summarize the argument in
> question?  I must admit it wouldn't have occurred to me to pick that as
> one of my primary criteria for judging languages (let alone
> programmers), I'm curious as to the reasoning?

See nearly any posting by Kent M. Pitman on comp.lang.lisp which
includes unwind-protect.  Here are a number of Message-IDs in the last 
couple of years:

<···············@world.std.com>
<···············@world.std.com>
<···············@world.std.com>   <--- This is probably quite relevant.
<···············@world.std.com>   <--- This too.
<···············@world.std.com>
<···············@world.std.com>

I think anyone seriously thinking about language use or design should
read all of the above...

Regs, Pierre.

-- 
Pierre Mai <····@acm.org>         PGP and GPG keys at your nearest Keyserver
  "One smaller motivation which, in part, stems from altruism is Microsoft-
   bashing." [Microsoft memo, see http://www.opensource.org/halloween1.html]
From: Pierre R. Mai
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <873dq8qmpp.fsf@orion.dent.isdn.cs.tu-berlin.de>
····@acm.org (Pierre R. Mai) writes:

> See nearly any posting by Kent M. Pitman on comp.lang.lisp which
> includes unwind-protect.  Here are a number of Message-IDs in the last 
> couple of years:
> 
> <···············@world.std.com>
> <···············@world.std.com>
> <···············@world.std.com>   <--- This is probably quite relevant.
> <···············@world.std.com>   <--- This too.
> <···············@world.std.com>
> <···············@world.std.com>
> 
> I think anyone seriously thinking about language use or design should
> read all of the above...

For users of Deja, the following URL should give you all of the above
articles (and some more).  Read from early dates to late dates...

http://www.deja.com/[ST_rn=ps]/qs.xp?ST=PS&svcclass=dnyr&QRY=unwind-protect&defaultOp=AND&DBS=1&OP=dnquery.xp&LNG=ALL&subjects=&groups=comp.lang.lisp&authors=Pitman&fromdate=Jan+1+1998&todate=Jan+1+1999&showsort=date&maxhits=100

Regs, Pierre.

-- 
Pierre Mai <····@acm.org>         PGP and GPG keys at your nearest Keyserver
  "One smaller motivation which, in part, stems from altruism is Microsoft-
   bashing." [Microsoft memo, see http://www.opensource.org/halloween1.html]
From: Russell Wallace
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38C059B3.528D@iol.ie>
Pierre R. Mai wrote:
> For users of Deja, the following URL should give you all of the above
> articles (and some more).  Read from early dates to late dates...

Ah, thanks!  Interesting articles.  I don't entirely agree with the
point at issue, but I do understand it now.

-- 
"To summarize the summary of the summary: people are a problem."
Russell Wallace
···············@iol.ie
From: Natarajan Krishnaswami
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <89mu3h$j4q$1@pale-rider.INS.CWRU.Edu>
On Thu, 02 Mar 2000 20:15:32 +0000, Russell Wallace <········@iol.ie> wrote:
> Can you give a reference to this, or summarize the argument in
> question?  I must admit it wouldn't have occurred to me to pick that as
> one of my primary criteria for judging languages (let alone
> programmers), I'm curious as to the reasoning?

I don't know Kent Pitman's argument, but IMO it says a great deal about
the commitment of the language designers (and indeed, the language
community) to the possibility of writing robust code.  Cleaning up after
exceptional conditions is one of the central concepts in constructing
reliable software, and it speaks volumes about languages where that's
not syntactically trivial to perform.


<N/>
-- 
  you have been evaluated.  you have a negative reference count.  prepare
  to be garbage collected.  persistence is futile.
	-- Erik Naggum
From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3161052909493352@naggum.no>
* Russell Wallace <········@iol.ie>
| Can you give a reference to this, or summarize the argument in question?

  Pierre R. Mai relieved me (thanks!) of searching for the articles where
  Kent has made this point, but my understanding of this issue is that any
  language that has the ability to do non-local transfers of control needs
  a mechanism to ensure that invariants and pre- and post-conditions are
  maintained even across them.  that is, _if_ you care about maintaining
  invariants and pre- and post-conditions (which could collectively be
  thought of the very sanity of your code), and that's where I extend this
  argument to apply to programmers.  most modern languages now have several
  sometimes _very_ powerful means of non-local transfers of control, such
  as exception handling.  outside of Common Lisp, none of them make sanity
  maintenance convenient, what with all the declarations and "try" blocks
  and everything.  a programmer who doesn't care about the sanity of his
  code and doesn't even pause to consider the consequences of modifying the
  state of a global variable (and they do exist, regardless of what people
  think or do to avoid them -- consider data on disk the ultimate in global
  variables) should just not be programming anything that has side effects.
  and the more we think about this, the more we want heavy-duty transaction
  processing and committing blocks of changes at a time, with roll-back and
  journaling and all that nifty stuff that the database people have figured
  out and automatized for their programmers.  unwind-protect is a similar
  concern for the sanity of code and data.  and binding special variables
  without needing unwind-protect to set and restore the values of otherwise
  mere global variables is on par with automatized transaction processing
  in terms of programmer convenience.  now somebody wants to take that
  convenience away from us with more verbose syntax and added hairiness to
  the language.  consider what database programmers would think about a
  proposal to have to be _explicit_ about every transaction processing step
  _all_ the time.  that's how good programmers should react to any measure
  to abridge the usefulness and convenience of special variables.

#:Erik
From: Lieven Marchand
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <89pfu9$1r$1@newnews1.news.nl.uu.net>
Erik Naggum <····@naggum.no> writes:

>   argument to apply to programmers.  most modern languages now have
>   several sometimes _very_ powerful means of non-local transfers of
>   control, such as exception handling.  outside of Common Lisp, none
>   of them make sanity maintenance convenient, what with all the
>   declarations and "try" blocks and everything.

The best example of this was a series of 3 articles in "The C++
report" a few years ago in which some of the leading C++ gurus tried
to write a template stack class that was both exception safe and did
not leak memory no matter what the class of objects it was
instantiated with did. In the end, they had a complete mess of nested
try's and it still failed for one very pathological case (a destructor
that throwed an exception IIRC).

-- 
Lieven Marchand <···@bewoner.dma.be>
If there are aliens, they play Go. -- Lasker
From: Harley Davis
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38c067f5$0$234@newsreader.alink.net>
Erik Naggum <····@naggum.no> wrote in message
·····················@naggum.no...
> * Russell Wallace <········@iol.ie>
> | Can you give a reference to this, or summarize the argument in question?
>
>   Pierre R. Mai relieved me (thanks!) of searching for the articles where
>   Kent has made this point, but my understanding of this issue is that any
>   language that has the ability to do non-local transfers of control needs
>   a mechanism to ensure that invariants and pre- and post-conditions are
>   maintained even across them.  that is, _if_ you care about maintaining
>   invariants and pre- and post-conditions (which could collectively be
>   thought of the very sanity of your code), and that's where I extend this
>   argument to apply to programmers.  most modern languages now have
several
>   sometimes _very_ powerful means of non-local transfers of control, such
>   as exception handling.  outside of Common Lisp, none of them make sanity
>   maintenance convenient, what with all the declarations and "try" blocks
>   and everything [...]

In Java there is unwind-protect:

try {
  ... some code that might throw an exception ...
} finally {
  ... clean up even if nonlocal xfer of ctrl ...
}

The thing that makes the Lisp unwind-protect much more useful is that it can
be combined with macros to implement control abstractions that clean up
after themselves properly, like with-open-file.

-- Harley
From: Christopher C Stacy
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <x8ld7pd2jgr.fsf@world.std.com>
At MIT back in the days of PDP-10 MACLISP, before Scheme, there was a
competing programming language called MDL.  It's most popular claim to 
fame is that it was the language that ZORK was written in.

MDL had infix syntax operators that made a symbol evaluate globally
or locally.   I have forgotten the exact way it worked, but it was
something like:   ,A  is the special A and .A  was the lexical A.
And I am sure there was a default for just  A   but I forget which.

The original designers of Scheme, and the developers of MACLISP and
of ZetaLisp (the predecessor of Common Lisp) were familiar with MDL.
From: Frank A. Adrian
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <RwHv4.5188$a82.62626@news.uswest.net>
Erik Naggum <····@naggum.no> wrote in message
·····················@naggum.no...
> | The issue is not just one of querying.  It's also one of control.
There's
> | no way to undo the effects of a defvar short of uninterning the symbol.
>
>   so let's find a way to do that, instead, then.  (how hard can this be?)

Well, the problem is that it's a nonsensical idea in the first place.
Unless I'm mistaken (and I'm sure Eric will tell me if I am :-), as defvar
is the same as creating a global symbol, proclaiming it special, and
(possibly) setting its symbol-value slot to a value, undoing it would be
unbinding the value, proclaimimg the variable no longer special,  and
destroying the global symbol.  Since the value would be unbound from the
symbol by its destruction anyway (and the proclaimation would be senseless),
you might as well not do it.  In, other words, the inverse operation for
defvar IS unintern.

If Erran doesn't like the term unintern, here's a nice macro for him:

(defmacro undefvar (var) `(unintern ',var)) ;pardon my indentation...

faa
From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3161053303848931@naggum.no>
* "Frank A. Adrian" <·······@uswest.net>
| In, other words, the inverse operation for defvar IS unintern.

  unintern nukes the property list, the home package, and the functional
  value of the symbol, as well as the identity of the symbol should there
  be any hold-over pointers to it after re-interning.  defvar affects none
  of these.  defvar also does not intern the symbol to begin with.  ergo,
  unintern is in no way the inverse of defvar.  case dismissesd.

  makunbound causes a subsequent defvar to initialize the value of the
  variable, so clearly there is an inverse relationship right there.  since
  there is no need or desire to nuke the _symbol_ (especially not with all
  its other properties), we only need an inverse operation for the special
  property of the symbol.  I have provided that as code for Allegro CL, as
  a stepping stone to a supported language mechanism.

#:Erik
From: Frank A. Adrian
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <t0%v4.922$3z4.41948@news.uswest.net>
My understanding of the operation was incomplete.  Thank you for the
correction.
faa

Erik Naggum <····@naggum.no> wrote in message
·····················@naggum.no...
> * "Frank A. Adrian" <·······@uswest.net>
> | In, other words, the inverse operation for defvar IS unintern.
>
>   unintern nukes the property list, the home package, and the functional
>   value of the symbol, as well as the identity of the symbol should there
>   be any hold-over pointers to it after re-interning.  defvar affects none
>   of these.  defvar also does not intern the symbol to begin with.  ergo,
>   unintern is in no way the inverse of defvar.  case dismissesd.
>
>   makunbound causes a subsequent defvar to initialize the value of the
>   variable, so clearly there is an inverse relationship right there.
since
>   there is no need or desire to nuke the _symbol_ (especially not with all
>   its other properties), we only need an inverse operation for the special
>   property of the symbol.  I have provided that as code for Allegro CL, as
>   a stepping stone to a supported language mechanism.
>
> #:Erik
From: Tim Bradshaw
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <ey3ln40jrbe.fsf@cley.com>
* Frank A Adrian wrote:
> Well, the problem is that it's a nonsensical idea in the first place.
> Unless I'm mistaken (and I'm sure Eric will tell me if I am :-), as defvar
> is the same as creating a global symbol, proclaiming it special, and
> (possibly) setting its symbol-value slot to a value, undoing it would be
> unbinding the value, proclaimimg the variable no longer special,  and
> destroying the global symbol.  Since the value would be unbound from the
> symbol by its destruction anyway (and the proclaimation would be senseless),
> you might as well not do it.  In, other words, the inverse operation for
> defvar IS unintern.

No, it's not.  DEFVAR doesn't intern or do anything like that (the
reader does that).  Uninterning the symbol is much too strong an
antidote.

--tim
From: Erann Gat
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <gat-0203000808490001@milo.jpl.nasa.gov>
In article <················@naggum.no>, Erik Naggum <····@naggum.no> wrote:

> * Erann Gat

> | The issue is not just one of querying.  It's also one of control.  There's
> | no way to undo the effects of a defvar short of uninterning the symbol.
> 
>   so let's find a way to do that, instead, then.  (how hard can this be?)

Pretty hard, apparently.  My first choice would have been to add
(declare (lexical ...))  But that was tried and rejected be people
who understand the problem much better than I do.

> | Maybe it would help to review the distinction between a variable and a
> | symbol (and the name of a symbol) just to make sure we are all on
> | the same page.
> 
>   find, but sometimes, it isn't everybody else who need to be on your page.

N.B.  The Common Lisp Standard uses the word "name" in two differenct
senses.  It can mean a string assocated with a symbol (the symbol-name)
or it can mean a symbol (or some other object) associated with a
variable or binding (the Standard makes variable a synonym for binding).
When I wrote my response I thought Erik was using the word "name" in
the first sense.  Last night I discovered the second meaning and
decided that he must have meant it in the second sense.  Now it
appears that I was right all along and he was just changing the subject.

> | The point is that none of this has anything to do with symbol names.
> 
>   duh.  I'm trying to redirect your attention to a worth-while problem,
>   entirely _away_ from messing with stuff you shouldn't be messing with.

Thank God we have Erik to guide us to worthwhile problems!

>   and IMNSHO, it isn't bad at all.  I have pointed out that we need a few
>   accessors into the environment to solve your uncertainty problem, and
>   perhaps we need a `notspecial' or `lexical' declaration to be able to
>   undo the pervasive effects of the `special' declaration

Like I said, this was proposed and rejected.  Why beat a dead horse?

>   however, I care
>   so much about the language that I'm unwilling to consider your proposal
>   when I understand the issues so much better than you do and I consider
>   your proposal to be a major disturbance over a petty issue that mainly
>   has to do with a disportional sense of uncertainty.

And I care so much about the language that I'm unwilling to drop the
matter just because some arrogant self-appointed guru says I should.

BTW, why would adding a LEXICAL declaration be any less disruptive
than allowing variable names of the form (special X)?  The vendors
would still have to change their implementations to support it.
Unlike other declarations, you can't ignore SPECIAL/LEXICAL declarations
and still preserve correct semantics.  This fact alone indicates that
declarations are the wrong place for this information.

> | Works the way I'd expect it to.
> 
>   so try typing in (setf (readtable-case *readtable*) :upcase) and tell me
>   what you expect to happen and/or that this is not a useful thing to do.
>   (note again that this is no longer a question of special variables.)

I would expect to have to hold down the shift-lock key before I could
set the readtable case back to upcase.  Honestly, I don't see the problem
here.

E.
From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3161015458973462@naggum.no>
* Erann Gat
| Pretty hard, apparently.  My first choice would have been to add (declare
| (lexical ...))  But that was tried and rejected be people who understand
| the problem much better than I do.

  proposals are rejected or adopted in context.  if a good idea is served
  alone or in a context that is not conducive to furthering principles that
  are valued higher by others than some small improvement, it will, as it
  should, be rejected.  how can _anyone_ have a problem understanding this?
  have you never proposed something, had it rejected, then seen it picked
  up by others only to be adopted?  this is clearly not because people hate
  you, but because you didn't do your homework, and somebody else did.

| Thank God we have Erik to guide us to worthwhile problems!

  huh?  were you _consciously_ trying to guide us to a _worthless_ problem,
  or is it wrong for _me_ to guide to worthwhile problems, while _you_ can
  pick worthwhile problems at will?  no wonder your proposals don't get
  accepted if this is how you deal with contributions.  sheesh!

| >   and IMNSHO, it isn't bad at all.  I have pointed out that we need a few
| >   accessors into the environment to solve your uncertainty problem, and
| >   perhaps we need a `notspecial' or `lexical' declaration to be able to
| >   undo the pervasive effects of the `special' declaration
| 
| Like I said, this was proposed and rejected.  Why beat a dead horse?

  I feel like I'm spoonfeeding a child.  it's because it's a question of
  getting agreement among people who have already made up their mind about
  a number of issues you may not know about, and this means you must not
  piss people off with pure _drivel_.  as I have strongly indicated, your
  inclusion of silly new syntax is a _good_ reason to reject all of your
  proposal.  like the old saying goes, with all this shit, there must be a
  pony somewhere, take away the crud, and what's left may not be a dead
  horse.  but feel free to blame somebody for your failure to get agreement.

| And I care so much about the language that I'm unwilling to drop the
| matter just because some arrogant self-appointed guru says I should.

  oh, geez, get _over_ yourself.  what's this, the emperor's new argument?
  who do you think you're fooling?

  isn't it just _too_ odd how often some doofus "self-appoints" someone
  _else_ to some status to which they themselves would never actually
  _self_-appoint themselves?  what's the point with such dishonesty and
  such incredible silly behavior as to pretend that others _self_-appoint
  themselves when in fact there's a lunatic at large who does both the
  appointing and the accusation of such appointing all by himself?
  whatever is _wrong_ with you?  you've come up with a bunch of really bad
  thinking and it must be shot down fast before you revamp the whole
  language, but still, there are a few good things in there and there's
  some work that can be turned into productive ideas and proposals, but
  what do you do?  you're only being silly and negative and concentrate on
  dead horses and rejection.  and now you're out picking a silly fight?
  what's the _point_ with this?  pull yourself _together_, damnit!

| BTW, why would adding a LEXICAL declaration be any less disruptive than
| allowing variable names of the form (special X)?  The vendors would still
| have to change their implementations to support it.  Unlike other
| declarations, you can't ignore SPECIAL/LEXICAL declarations and still
| preserve correct semantics.  This fact alone indicates that declarations
| are the wrong place for this information.

  well, I don't generally and didn't now make just one big proposal and
  feel personally defeated when it was rejected as a silly idea.  believe
  it or not, but I have tried to figure out what would completely supersede
  your silly idea such that even you would be happier with the solution.
  this, however, is doomed to fail miserably as long as you only take the
  negative views on everything, completely ignore the good stuff (notice
  that I don't) I say, and huff and puff a lot instead of trying to solve
  the _problem_ you have, the _adopted_ solution to which is very unlikely
  to be whatever you dreamt up to begin with, anyway.  you're not being
  constructive about this at all.  that annoys me to no end, because you
  raise issues that need to be resolved, and the way you go about it, it's
  unlikely that we will very find the consensus to resolve them.  again,
  pull yourself together, damnit!

| > | Works the way I'd expect it to.
| > 
| >   so try typing in (setf (readtable-case *readtable*) :upcase) and tell me
| >   what you expect to happen and/or that this is not a useful thing to do.
| >   (note again that this is no longer a question of special variables.)
| 
| I would expect to have to hold down the shift-lock key before I could
| set the readtable case back to upcase.  Honestly, I don't see the problem
| here.

  OK, could you explain why it is unreasonable to think that holding down
  the shift key while typing that line in is a _misfeature_?  can you
  explain why it is unreasonable to give a conforming Common Lisp system
  the ability to deal with :preserve _and_ lower-case, like beginners and
  experts alike see in all the textbooks and examples on the Net and which
  they have come to expect from _other_ languages they use?

  I'm doing this also as an experiment to see if you can at all relate to
  what other people tell you about their problems, since I have evidence
  that you have a very hard time dealing with stuff you don't dream up on
  your own, and if you can at least show that you can wrap your head around
  another problematic issue, there might be grounds for figuring out what
  would _really_ solve your other problems, without _having_ to accept your
  proposals verbatim.  as I said, you have raised certain relevant issues
  that I think are quite important, but only to be met with childish
  bickering and an _incredibly_ stupid "self-appointed guru", instead of a
  desire to help resolve the parts of your concerns that others respond
  _well_ to.  I could do without the rampant stupidity, so what _is_ your
  problem?  exercise some mental _focus_, dude!

  sheesh!

#:Erik
From: Erann Gat
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <gat-0203001707110001@milo.jpl.nasa.gov>
In article <················@naggum.no>, Erik Naggum <····@naggum.no> wrote:

> | > | Works the way I'd expect it to.
> | > 
> | >   so try typing in (setf (readtable-case *readtable*) :upcase) and tell me
> | >   what you expect to happen and/or that this is not a useful thing to do.
> | >   (note again that this is no longer a question of special variables.)
> | 
> | I would expect to have to hold down the shift-lock key before I could
> | set the readtable case back to upcase.  Honestly, I don't see the problem
> | here.
> 
>   OK, could you explain why it is unreasonable to think that holding down
>   the shift key while typing that line in is a _misfeature_?  can you
>   explain why it is unreasonable to give a conforming Common Lisp system
>   the ability to deal with :preserve _and_ lower-case, like beginners and
>   experts alike see in all the textbooks and examples on the Net and which
>   they have come to expect from _other_ languages they use?

OK, I'll bite.

People are used to languages that are case-sensitive, where the default
readtable-case (indeed the only readtable-case available to them) is
:preserve, and where most keywords are lower case, or a mix of primarily
lower case with some upper case.

Common Lisp is case-sensitive like people expect.  But the default
readtable case is :upcase rather then :preserve, and the keywords
(i.e. the names of the standard symbols) are all upper case.

I don't know whether this last item is part of the standard or simply a
consequence of the default read table case being :upcase.

In any case, to make CL act like every other language out there we'd
have to 1) change the default readtable-case to :preserve and 2) change
the names of all the standard symbols.  If (setf (symbol-name ...) ...)
were legal this would be easy, but it isn't, so it's not.  Straightforward
implementation-specific hacks won't work because the symbol name is
stored in many places, not just in the symbol.  In MCL:

? (setf y 'x)
X
? (setf (uvref 'x 0) "x")
"x"
? y
#|symbol not found in home package!!|#COMMON-LISP-USER::\x
? 

You could make duplicate symbols with lower-case names and copy their
value, function, and plist slots, but this would probably break
most compilers, which probably have code like (case (car form) (if ...

You could change INTERN to use STRING-EQUAL instead of STRING= when
determining whether a symbol already exists or not.

Or you could just tell beginners not to mess with readtable-case at all
since the :upcase default generally does the Right Thing.

E.
From: Frank A. Adrian
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3FIv4.5484$a82.68795@news.uswest.net>
Erann Gat <···@jpl.nasa.gov> wrote in message
·························@milo.jpl.nasa.gov...

> People are used to languages that are case-sensitive, where the default
> readtable-case (indeed the only readtable-case available to them) is
> :preserve, and where most keywords are lower case, or a mix of primarily
> lower case with some upper case.

People are also used to languages that need explicit type declarations
everywhere, all the time, too.  This does not mean that it would be a GOOD
thing to add this to Lisp.  What you seem to be espousing is that no one who
has ever learned any language should ever be surprised by the features of
another.  The only way to achieve this would be to have only a single
language.  As long as this is Lisp, I have no problem with this :-).
Otherwise, I believe that your goal is misguided.

> Common Lisp is case-sensitive like people expect.  But the default
> readtable case is :upcase rather then :preserve, and the keywords
> (i.e. the names of the standard symbols) are all upper case.

And there is good historical precedence for doing so.  One of the Common
Lisp standard committee's jobs was to unify the common threads of that
time's current diverging implementations.  This meant attempting not to
break existing code if possible.  Almost all of the then current Lisp
implementations had this feature.

> I don't know whether this last item is part of the standard or simply a
> consequence of the default read table case being :upcase.

See above.  It was done to not gratuitously break as much code as possible.

>
> In any case, to make CL act like every other language out there...

And this is good how?

> ...we'd
> have to 1) change the default readtable-case to :preserve

And have to sort through tons of compiler warnings or run time errors in
existing code.  And for what?

> ... and 2) change
> the names of all the standard symbols.

Which really would be insane.

> If (setf (symbol-name ...) ...)
> were legal this would be easy,

Why SHOULD it be legal?  setf'ing a symbol-name slot could lead to more
trouble than anything ever suggested.

> but it isn't, so it's not.

And thank God (or the ANSI comittee) for that.

> Straightforward
> implementation-specific hacks won't work because the symbol name is
> stored in many places, not just in the symbol.

Actually, the symbol-name may only be stored in one place, it may be stored
in many places, and it may not be stored anywhere.  The only thing the spec
says is how that symbol is supposed to behave functionally, not
implementationally.  As far as we know, some implementation, somewhere, may
store its symbol-name slot up your ass.

You know, I'm beginning to think that Erik is right and you really are a
brick.

faa
From: Coby Beck
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <_7Kv4.2048$eh.244613@news.bc.tac.net>
Frank A. Adrian <·······@uswest.net> wrote in message
·························@news.uswest.net...
> Erann Gat <···@jpl.nasa.gov> wrote in message
> ·························@milo.jpl.nasa.gov...
>
> You know, I'm beginning to think that Erik is right and you really are a
> brick.
>
> faa
>

What an assinine comment.

People who throw insults like this around so casually should get back in
touch with the rest of humanity and understand that it does NOTHING but
weaken whatever argument they are really trying to make.  Ad Hominum is the
last gasp of the desperate loser, so if you really do have an intelligent
contribution (as many with this contemptible style seem to) why degrade it
with such childish potshots?

Coby
From: Erann Gat
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <gat-0303001127310001@milo.jpl.nasa.gov>
In article <····················@news.uswest.net>, "Frank A. Adrian"
<·······@uswest.net> wrote:

> You know, I'm beginning to think that Erik is right and you really are a
> brick.

And I'm beginning to think that Erik is right, and stupid assholes like
you ought to be dealt with harshly and severely.  But I find I just don't
have the master's talent for vitriol (nor the stomach for it).

You quoted almost everything I wrote execpt:

> Or you could just tell beginners not to mess with readtable-case at all
> since the :upcase default generally does the Right Thing.

This might have been a clue to you that I don't really think that
there's a problem with how CL handles case.

Now I'll follow Erik's example again and invite you to think (if you
are capable of it) about why I might have written what I did despite
the fact that I don't see a proble with how CL handles case.

E.
From: Coby Beck
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <952115459222@NewsSIEVE.cs.bonn.edu>
Erann Gat <···@jpl.nasa.gov> wrote in message
·························@milo.jpl.nasa.gov...
| In article <····················@news.uswest.net>, "Frank A. Adrian"
| <·······@uswest.net> wrote:
|
| > You know, I'm beginning to think that Erik is right and you really are a
| > brick.
|
| And I'm beginning to think that Erik is right, and stupid assholes like
| you ought to be dealt with harshly and severely


No, this is not right.  Just have more patience.  People with an ounce of maturity know
how to ignore that kind of behavior and will not let their opinion of you or what you
write be influenced in this way.  The only good way to  deal with comments like that is
to stay above it.

I guarantee you that i am not the only one who finds these constant put-downs to be
repugnant and a waste of everyone's time.

Coby
From: Erik Naggum
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <3161103283096688@naggum.no>
* Erann Gat
| Common Lisp is case-sensitive like people expect.

  we might as well conclude at this time that special variables work just
  the way people expect, because we make a semi-conscious decision to
  ignore those values of "people" where "expect" returns false.  _some_
  people, however, do not expect the same as you do, and they might even
  react the same way you do to some aspect of special variables ("it's
  EVIL!") to some aspects of upper-case symbol names.  it's _so_ amusing
  that you don't get this.

  the point being, put like a nice little riddle: those who have problems
  with symbol-value are also likely have problems with symbol-name.

| I don't know whether this last item is part of the standard or simply a
| consequence of the default read table case being :upcase.

  the symbols are all upper-case and Lisp has case conversion because the
  languages that Lisp talked to had upper-case names and case conversion,
  FORTRAN in particular.  since symbols are first-class citizens in Lisp,
  and not in most other languages, we have been stuck with them in a way
  that other languages haven't.  other languages have moved on to a much
  richer character set (the upper-case thing was merely an artifact of the
  terminal equipment and punched cards on which the code was written) and
  have dispensed with case conversion because it loses information that is
  now more readily available.

| In any case, to make CL act like every other language out there we'd have
| to 1) change the default readtable-case to :preserve and 2) change the
| names of all the standard symbols.

  that's the straightforward answer, but now you're going into this
  "there's only one solution to this problem, and that's the one I just
  dreamt up, but since I didn't like the problem, I dreamt up a bad
  solution, so therefore the problem is also bad" mode which seems to have
  an incredible attraction to you.  I'm explicitly trying to get you _off_
  of that path.  can you work with me on this, please?

  Allegro CL has the ability to do just what you're describing, and has had
  it forever because of the Franz Lisp legacy -- it was lower-case and case
  sensitive.  today, excl:set-case-mode actually converts symbol names from
  upper-case to lower-case.  Allegro CL is actually built with lower-case
  symbol names, upper-cased as a step in building the distributed version
  to customers.  this is not a problem for Franz Inc, and not a problem for
  their customers.  many customers also revert to lower-case mode simply
  because it makes a lot more sense than upper-case mode does at this time.
  that they don't talk about it has to do with the fact that some people
  get _really_ upset whenever case is brought up, but it finally dawned on
  me that we're _not_ talking about case, we're talking about which other
  languages we want to communicate with, and case issues _follow_ from
  that.  it's not as if case is the primary factor of choice and we just
  happen to like FORTRAN better than C.  it's that to talk to FORTRAN, you
  had to use the same case FORTRAN did, which were upper-case, but to talk
  to C, you have to use the same case C does, which is in both cases.  it's
  a question of communication.  of course, we can demand that other people
  talk to us, and refuse to listen to their arguments.  people who do that
  on an habitual basis in real life, too, probably stick with upper-case in
  Common Lisp, as well.

  yet, however you wish to regard this, case-swapping is not something you
  do without vendor support.  Allegro CL already has all the support it
  needs.  in the case of CLISP or CMUCL, you're free to fix it yourself in
  any way you want that doesn't have to be "portable" at all.  that leaves
  us with what Harlequin and Digitool would do if they were asked.

| Straightforward implementation-specific hacks won't work because the
| symbol name is stored in many places, not just in the symbol.

  so let's do non-straightforward implementation-specific hacks, then.
  (again, how hard can it possibly be to realize that when you have found
  an obvious flaw in a given _solution_, you keep looking for solutions,
  you don't just give up and shout the _inverse_ of "eureka!" and declare
  the _problem_ dead and buried.)

| You could make duplicate symbols with lower-case names and copy their
| value, function, and plist slots, but this would probably break
| most compilers, which probably have code like (case (car form) (if ...

  again, I would prefer to engage the creative part of the brain, not the
  propaganda machine, when we encounter engineering problems.  obviously,
  this idea is really stupid, and so it's an indirect insult to would-be
  proposers to assume that they haven't even thought about it.  but, hey,
  this is also something I'm trying to get you away from resorting to.

  Common Lisp is often hailed as suitable for writing mini-languages.  now,
  instead of writing a _new_ mini-language, I think it's important that we
  find a way for a fully conforming ANSI Common Lisp implementation to be
  able to handle source code in :preserve mode, written in lower-case.
  this is _obviously_ not a problem, since Common Lisp is good at writing
  mini-languages.  right?  right!  let's see if it is possible to turn code
  written with :preserve and lower-case expectations into code that can be
  compiled without changing much anything.  this should be eminently doable
  for the vast majority of cases.  (if there be residiual problems, I hope
  we can avoid more propaganda machine output and instead focus on solving
  them or theorizing about the problems, not just sit down and wimper.)

| Or you could just tell beginners not to mess with readtable-case at all
| since the :upcase default generally does the Right Thing.

  and that's what I've been telling you to do with your "special" hacks.
  I'm relieved that you think this is an OK response to a silly proposal,
  but in this case, I'm trying to show you that my proposal, which I sort
  of expected you to dislike, is actually quite similar to your problem:
  how to get people's expectations to fit the language they use, and vice
  versa.  you can't dismiss this _problem_, and I certainly did not dismiss
  it in your proposals, but you can still dismiss proposed solutions.
  that's why I wanted you to see the difference between bundling a problem
  with a solution and having it rejected and looking a problem square in
  the eye and determine to solve it by submitting a whole bunch of ideas
  for other people's rejection and perhaps that one winner.

#:Erik
From: Erann Gat
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <gat-0603001118410001@milo.jpl.nasa.gov>
In article <················@naggum.no>, Erik Naggum <····@naggum.no> wrote:

> * Erann Gat
> | Common Lisp is case-sensitive like people expect.
> 
>   we might as well conclude at this time that special variables work just
>   the way people expect, because we make a semi-conscious decision to
>   ignore those values of "people" where "expect" returns false.

Pardon my imprecision.  CL is case-sensitive like people who expect CL
to be like other languages expect (since other languages are case
sensitive).  Why pick this nit?

> | In any case, to make CL act like every other language out there we'd have
> | to 1) change the default readtable-case to :preserve and 2) change the
> | names of all the standard symbols.
> 
>   that's the straightforward answer, but now you're going into this
>   "there's only one solution to this problem, and that's the one I just
>   dreamt up, but since I didn't like the problem, I dreamt up a bad
>   solution, so therefore the problem is also bad" mode which seems to have
>   an incredible attraction to you.  I'm explicitly trying to get you _off_
>   of that path.  can you work with me on this, please?

Well, I'm trying.  Keep in mind, *I* personally don't think there's
anything wrong with the way CL handles case.  *You* posed this problem
as an excercise, and I'm approaching it that way.  But please stop
confusing how I attack a hypothetical problem with what I really think.

I suppose there are other ways to make CL act like other languages
(assuming that were a desirable thing to do, which I do not necessarily
believe).  We could, for example, make INTERN use STRING-EQUAL rather
than STRING= in determining whether a symbol already exists in a package.
There may be other solutions.  I don't know, and I don't really care.

> | Or you could just tell beginners not to mess with readtable-case at all
> | since the :upcase default generally does the Right Thing.
> 
>   and that's what I've been telling you to do with your "special" hacks.

Ah, that's what I suspected.

This will undoubtedly come as a shock to you: I don't care nearly as much
about this special variable thing as you seem to think I do.  I don't have
any emotional investment in it.  If it gets rejected, I don't really care.

>  I'm relieved that you think this is an OK response to a silly proposal,

It's even an OK response to a non-silly proposal.

>  but in this case, I'm trying to show you that my proposal,

What proposal?  I don't recall you making any proposal.  I recall you
posing a (straw man) problem.  That is not the same thing as making a
proposal.

>  that's why I wanted you to see the difference between bundling a problem
>  with a solution and having it rejected and looking a problem square in
>  the eye and determine to solve it by submitting a whole bunch of ideas
>  for other people's rejection and perhaps that one winner.

Fine.  Let's go back to the beginning.

CL has many problems.  IMO not a single one of them even comes close
in severity to the design flaws of other languages.  I am very happy with
CL just the way it is.  But it could be even better.  Most of CL's warts
are well known, and they include but are not limited to:

1.  How the reader works (including handling of case and the design of
the package system)
2.  Issues with dynamic vs. lexical bindings, including beginner's
confusion, and the fact that there is no portable way to write code that
is guaranteed to produce a lexical binding.

All of these problems have been extensively discussed in the past.  There
have been numerous proposals made on how to fix these problems, and differing
opinions on their severity and whether they need to be fixed at all (or
even if they are problems at all).

I wish to focus my attention on the second problem not because I think
it's severe, but because I think I have something new to add to the
discussion.  (I happen to think that the problem is quite severe, but I
readily concede that reasonable people can disagree.)

One solution to the problem that has received extensive attention in the
past is the addition of a LEXICAL declaration.  This proposal has not been
adopted for reasons that I don't fully understand.  (This is not to say
that I don't understand the technical issues involved, simply that I don't
know whether the proposal's not being adopted is a result of those issues
or the result of politics or other non-technical considerations.)

In any case, as long as the issue is still open for discussion here's
another proposal to throw into the mix: take lexical/special specifications
out of the declarations and put them in the lambda list instead.  I think
this is a good idea because:

1.  It's backwards-compatible.  Old code will continue to work in systems
that adopt this proposal.

2.  It allows you to table the thorny technical issue of lexical globals.
If the only place you can specify a lexical binding is in a lambda-list it
is impossible to create a lexical global and the problem can be deferred.

3.  It provides a stronger lexical association between a variable and how
it is bound.  It moves the language towards more uniformity in following
the principle that declarations are advice to the compiler for producing
more efficient code, not specifications of the actual semantics that the
compiler must not ignore.  In fact, SPECIAL is the ONLY declaration that
ALL implementations MUST process in order to produce correct code.  (The
other declarations that implementations must not ignore are NOTINLINE,
and SAFETY, but implementations can actually ignore those simply by
never inlining and always generating maximally safe code.)  This is a
serious non-uniformity that requires all implementations to process all
declarations simply to determine whether any of them are SPECIAL declarations.
IMO, this is a serious wart that this proposal would take a step towards
removing.

This proposal is not the only one that has these features.  For example,
adding a new binding form a la Scheme's FLUID-LET also shares all of these
features.  I make this proposal not because I think it's necessarily better
than any other, but simply because I have not seen it proposed before.

That said, the lambda-list proposal has three features that could be
perceived as advantages over the FLUID-LET proposal:

1.  It preserves the CL semantics of allowing both lexical and dynamic
bindings in the same binding form.

2.  It can be extended to allow multiple value binding and destructuring
binding to all be folded in to a single uniform framework.

3.  It's not the way Scheme does it.

That's it.  The proposal is now on the table.  If people don't like it,
fine.  Leave the language the way it is, or do something different.  I
really don't care.  CL is still the best programming language out there,
warts and all.  But that's no excuse not to try to make it better.

Erann Gat
···@jpl.nasa.gov
From: Tom Breton
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <m3ln3zebjz.fsf@world.std.com>
···@jpl.nasa.gov (Erann Gat) writes:

> 
> People are used to languages that are case-sensitive, where the default
> readtable-case (indeed the only readtable-case available to them) is
> :preserve, and where most keywords are lower case, or a mix of primarily
> lower case with some upper case.

> Common Lisp is case-sensitive like people expect.  But the default
> readtable case is :upcase rather then :preserve, and the keywords
> (i.e. the names of the standard symbols) are all upper case.

ISTM this is a bad thing.  One principle in programming is to make
your object names distinct (funciton names, variable names, whatever),
so they're not easily mistaken for each other.  

Now, incorporating a word-similarity metric into a programming
language to disallow too-similar names is obviously a huge chore.  But
one thing that can be done very easily is to disallow names that are
the same except for case.  Just fold case, and they're the names that
collide.

So IMO case-folding by default is a good thing.

-- 
Tom Breton, http://world.std.com/~tob
Not using "gh" since 1997. http://world.std.com/~tob/ugh-free.html.
Rethink some Lisp features, http://world.std.com/~tob/rethink-lisp/index.html
From: Tim Bradshaw
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <ey366v5gqhi.fsf@cley.com>
* Erann Gat wrote:

> Pretty hard, apparently.  My first choice would have been to add
> (declare (lexical ...))  But that was tried and rejected be people
> who understand the problem much better than I do.

But people working under constraints like getting the standard out the
door in reasonable time.  Just because it was rejected does not mean
it is not a reasonable thing to do.  Syntactic environment access was
also rejected.  A MOP is not in there.  Unless you know why it was
rejected you don't know whether it's a good idea.

--tim
From: Tim Bradshaw
Subject: Lisp and fox hunting (Re: A modest proposal (long))
Date: 
Message-ID: <ey33dq9gouy.fsf_-_@cley.com>
This whole thread reminds me of an article I once read on why the UK
government should not pass legislation banning fox hunting.

(If you're not in the UK you may not be aware of this issue: we have a
tradition of hunting foxes with dogs which is a fairly barbaric
process and also very much a class issue.  There is wide support for
banning it except among the country-based upper/upper-middle classes.)

The article started off by stating clearly that the author considered
fox hunting barbaric.  However it claimed that legislation should
*not* be worked on because there are an awful lot of other things
which are barbaric and should be stopped, and a lot of those do a lot
more damage to animals and people than fox hunting.  Since getting
legislation through takes time, and since getting anti fox hunting
legislation through was likely to be contentious and slow, the article
claimed that the best use of the finite time resources available was
to pass other legislation which had more benefit.

This is just like that.  Obviously having some better approach to
specials would solve some number of problems.  But there other things
that could be done, and there are finite resources to do them.  So
things need to be prioritised, based on what does the most good.

One way of working out the priorities
is to look at what vendors are doing.  If lots of people are
complaining at them about this issue, then they will start releasing
implementations with various solutions to the problem.  Vendors are
very simple creatures, driven largely by customer demand, so they
provide this nice experimental mechanism for discovering what the real
problems are.

Unfortunately vendors can suffer from the usual local-minimum problem
that you get with gradient descent.  But you can fix that.  If you
think this is a real problem, produce an implementation that fixes it
(start with one of the existing free CLs, make it do what you want).
If the issue is a real problem then people will soon be clamouring at
the vendors, and before you know it there will be n different
solutions to the problem.

At *that* point, it is appropriate to start thinking about making
changes to the standard language.

Complain at your vendor or produce an implementation which solves the
problem. But whatever you do, don't just sit there whining on c.l.l.
Far too many people do that.

--tim

(please do not assume this article tells you anything about my
position on fox hunting.)
From: Tim Bradshaw
Subject: Re: Lisp and fox hunting (Re: A modest proposal (long))
Date: 
Message-ID: <ey3zoshf6li.fsf@cley.com>
* Rajappa Iyer wrote:

> Really?

Yes, really!  I might like barbaric sports!
From: Tim Bradshaw
Subject: Re: Lisp and fox hunting (Re: A modest proposal (long))
Date: 
Message-ID: <ey3putdf4bj.fsf@cley.com>
* Rajappa Iyer wrote:

> Ah, my mistake.  I thought that `barbaric' was normally used as a
> pejorative. 

It is, I was just trying to escape from the pit I'd dug myself...

--tim
From: Kenneth P. Turvey
Subject: Re: Lisp and fox hunting (OFF TOPIC)
Date: 
Message-ID: <slrn8ch9p9.h04.kt-alt@pug1.sprocketshop.com>
On 02 Mar 2000 19:21:09 +0000, Tim Bradshaw <···@cley.com> wrote:
>This whole thread reminds me of an article I once read on why the UK
>government should not pass legislation banning fox hunting.
>
>(If you're not in the UK you may not be aware of this issue: we have a
>tradition of hunting foxes with dogs which is a fairly barbaric
>process and also very much a class issue.  There is wide support for
>banning it except among the country-based upper/upper-middle classes.)
[Snip]

Out of curiosity, what is the class issue?  Do the lower classes feel
left out?  

Also, would most of those objecting only object to hunting for sport or
would they also object if the game is consumed?  Would they object to
factory farming as practiced in the US (and I assume the UK).  

-- 
Kenneth P. Turvey <······@SprocketShop.com> 
--------------------------------------------
  One of the advantages of being disorderly is that one is constantly
  making exciting discoveries.  
        -- A. A. Milne




P.S.  I'm a vegetarian on moral grounds but I find the idea of banning
fox hunting somewhat laughable... no offense.
From: Robert Posey
Subject: Re: Lisp and fox hunting (OFF TOPIC)
Date: 
Message-ID: <38C9263A.F0CB7F0D@raytheon.com>
"Kenneth P. Turvey" wrote:
> 
> On 02 Mar 2000 19:21:09 +0000, Tim Bradshaw <···@cley.com> wrote:
> >This whole thread reminds me of an article I once read on why the UK
> >government should not pass legislation banning fox hunting.
> >
> >(If you're not in the UK you may not be aware of this issue: we have a
> >tradition of hunting foxes with dogs which is a fairly barbaric
> >process and also very much a class issue.  There is wide support for
> >banning it except among the country-based upper/upper-middle classes.)
> [Snip]
> 
> Out of curiosity, what is the class issue?  Do the lower classes feel
> left out?
> 
> Also, would most of those objecting only object to hunting for sport or
> would they also object if the game is consumed?  Would they object to
> factory farming as practiced in the US (and I assume the UK).

Its considered a Class Issue because of two things:
 1. First it is a sport largely reserved for the Upper Classes, and in the
    UK that means more than just money.  In the UK, Class issues are not
    just economic.

 2. Since traditional Fox Hunting involves a captured Fox, huntsmen, and 
 a large number of specially trained horses and dogs, it costs a whole 
 lot of money.  Lower economic classes can not form their own fox hunts
 any more than they can go bear hunting in Alaska.


My objection is that Fox Hunting is not hunting in the traditional sense.
They are hunting a capture or breed fox released at the proper time
to make the hunt enjoyable.  The use of dogs and huntsman make it a
game, not a hunt.  It deserves none of the positive associations that
true hunting does.  IT is more akin to the sick US practice of having
trophy lion hunts where somebody's discarded pet lion is released 
from a small cage briefly so some pathetic sportsman can shoot it and
claim he bagged a Lion.  I would think any true hunter would retch at
either sport.

Muddy
> 
> --
> Kenneth P. Turvey <······@SprocketShop.com>
> --------------------------------------------
>   One of the advantages of being disorderly is that one is constantly
>   making exciting discoveries.
>         -- A. A. Milne
> 
> P.S.  I'm a vegetarian on moral grounds but I find the idea of banning
> fox hunting somewhat laughable... no offense.
From: Janos Blazi
Subject: Re: Lisp and fox hunting (OFF TOPIC)
Date: 
Message-ID: <38c962d7_5@goliath.newsfeeds.com>
Isn't fox hunting simply *boring*? It is not much of an intellectual
challenge, is it? And the fox always looses in the end.  And is it true that
the most valuable trophy of the foy hunters is the Dr Doolitle cup?

Janos Blazi




-----= Posted via Newsfeeds.Com, Uncensored Usenet News =-----
http://www.newsfeeds.com - The #1 Newsgroup Service in the World!
-----==  Over 80,000 Newsgroups - 16 Different Servers! =-----
From: Stig E. Sandø
Subject: Re: Lisp and fox hunting (OFF TOPIC)
Date: 
Message-ID: <871z5i4ha6.fsf@palomba.bananos.org>
"Janos Blazi" <······@netsurf.de> writes:

> Isn't fox hunting simply *boring*? It is not much of an intellectual
> challenge, is it?

One is spending time in the countryside in fresh air with friends and
getting some exercise.  Later in the evening it's customary with
sizable meal and something fitting to drink.  Is there a better way to
spend a weekend?  What do you do when you want to spend quality-time
with friends out of town?   

> And the fox always looses in the end.

Yes.  Tragic, isn't it? 

-- 
------------------------------------------------------------------
Stig Erik Sandoe     ····@ii.uib.no    http://www.ii.uib.no/~stig/
From: Janos Blazi
Subject: Re: Lisp and fox hunting (OFF TOPIC)
Date: 
Message-ID: <38c96347_1@goliath.newsfeeds.com>
Isn't fox hunting simply *boring*? It is not much of an intellectual
challenge, is it? And the fox always looses in the end.  And is it true that
the most valuable trophy of the foy hunters is the Dr Doolitle cup?

Janos Blazi





-----= Posted via Newsfeeds.Com, Uncensored Usenet News =-----
http://www.newsfeeds.com - The #1 Newsgroup Service in the World!
-----==  Over 80,000 Newsgroups - 16 Different Servers! =-----
From: Dave Pearson
Subject: Re: Lisp and fox hunting (OFF TOPIC)
Date: 
Message-ID: <slrn8cidkg.bc2.davep.news@hagbard.demon.co.uk>
On Fri, 10 Mar 2000 10:43:38 -0600, Robert Posey <·····@raytheon.com> wrote:

> "Kenneth P. Turvey" wrote:
> > 
> > Out of curiosity, what is the class issue?  Do the lower classes feel
> > left out?
> > 
> > [SNIP]
> 
> Its considered a Class Issue because of two things:
>  1. First it is a sport largely reserved for the Upper Classes, and in the
>     UK that means more than just money.  In the UK, Class issues are not
>     just economic.

I think it is worth pointing out that the issue of hunting isn't cut across
clear class lines. Hunting can and does provide work for working class folk
who live in the country.

[Gross simplification alert] In my experience most of the people against fox
hunting either live in town or are middle class.

-- 
Take a look in Hagbard's World: | boxquote.el - "Boxed" text quoting.
http://www.hagbard.demon.co.uk/ |  sawmill.el - Sawmill mode.
http://www.acemake.com/hagbard/ |  uptimes.el - Record emacs uptimes.
emacs software, including.......| quickurl.el - Recall lists of URLs.
From: Gareth McCaughan
Subject: Re: Lisp and fox hunting (OFF TOPIC)
Date: 
Message-ID: <868zzqmu84.fsf@g.local>
Dave Pearson wrote:

> I think it is worth pointing out that the issue of hunting isn't cut across
> clear class lines. Hunting can and does provide work for working class folk
> who live in the country.
> 
> [Gross simplification alert] In my experience most of the people against fox
> hunting either live in town or are middle class.

In my experience most people either live in a town or are
middle class.

That is: although I know there are plenty of non-middle-class
country dwellers, they form a small proportion of the people
I know and an even smaller proportion of the people whose views
on fox hunting I know or can guess. Are you sure the same isn't
true of you too? (I'd guess it is for most people in c.l.l --
Usenet and programming are both pretty towny, middle-class
activities.)

-- 
Gareth McCaughan  ················@pobox.com
sig under construction
From: Dave Pearson
Subject: Re: Lisp and fox hunting (OFF TOPIC)
Date: 
Message-ID: <slrn8cjtkq.bc2.davep.news@hagbard.demon.co.uk>
On 10 Mar 2000 20:43:39 +0000, Gareth McCaughan <················@pobox.com> wrote:
> Dave Pearson wrote:
> 
> > I think it is worth pointing out that the issue of hunting isn't cut
> > across clear class lines. Hunting can and does provide work for working
> > class folk who live in the country.
> > 
> > [Gross simplification alert] In my experience most of the people against
> > fox hunting either live in town or are middle class.
> 
> In my experience most people either live in a town or are middle class.

<grin> Yeah, fair comment.

> That is: although I know there are plenty of non-middle-class country
> dwellers, they form a small proportion of the people I know and an even
> smaller proportion of the people whose views on fox hunting I know or can
> guess. Are you sure the same isn't true of you too? (I'd guess it is for
> most people in c.l.l -- Usenet and programming are both pretty towny,
> middle-class activities.)

Personally I live in the country so I guess I'm the exception. Yes, I take
your point about the obvious weighting of the view but what I was (badly?)
trying to say is that, in my experience, the issue isn't based around an
obvious class division (in my experience it is more of a town vs country
thing).

-- 
Take a look in Hagbard's World: | boxquote.el - "Boxed" text quoting.
http://www.hagbard.demon.co.uk/ |  sawmill.el - Sawmill mode.
http://www.acemake.com/hagbard/ |  uptimes.el - Record emacs uptimes.
emacs software, including.......| quickurl.el - Recall lists of URLs.
From: Tim Bradshaw
Subject: Re: Lisp and fox hunting (OFF TOPIC)
Date: 
Message-ID: <ey3g0tyn2uz.fsf@cley.com>
Please, if there needs to be a discussion about this could it be
somewhere else.  I will feel guilty for ever if I feel I've triggered
one, and will have to go and hide in a corner for the rest of my life
or something.

--tim
From: His Holiness the Reverend Doktor Xenophon Fenderson, the Carbon(d)ated
Subject: How does UNWIND-PROTECT work? (was Re: A modest proposal (long))
Date: 
Message-ID: <w4owvn62pce.fsf_-_@nemesis.irtnog.org>
>>>>> "EN" == Erik Naggum <····@naggum.no> writes:

    EN> (if [programmers] know about unwind-protect -- Kent Pitman has
    EN> made the cogent argument that languages can be judged on the
    EN> existence of such a language feature -- I'll argue that the
    EN> same applies to programmers and whether they know about it).

I confess I've never understood UNWIND-PROTECT.  Would someone explain
what it does, please?  Things like UNWIND-PROTECT (in Common Lisp) and
CALL/CC (in Scheme) have this aura of heavy wizardry surrounding them,
mostly because I've never understood how they work and for what one
would use them.

Regards,
#\X

-- 
"There is no spoon" - Neo, The Matrix
"SPOOOOOOOOON!" - The Tick, The Tick
"Redeyes! Didn't expect to see you so... SPOON!" - The Blue R
From: thi
Subject: Re: How does UNWIND-PROTECT work? (was Re: A modest proposal (long))
Date: 
Message-ID: <m2rsnxuggx3.fsf@netcom9.netcom.com>
"His Holiness the Reverend Doktor Xenophon Fenderson, the Carbon(d)ated" <········@irtnog.org> writes:

> I confess I've never understood UNWIND-PROTECT.  Would someone explain
> what it does, please?  Things like UNWIND-PROTECT (in Common Lisp) and
> CALL/CC (in Scheme) have this aura of heavy wizardry surrounding them,
> mostly because I've never understood how they work and for what one
> would use them.

could you explain your efforts to date at understanding these concepts?
that might help people to see a path of explanation.

thi
From: markku laukkanen
Subject: Re: How does UNWIND-PROTECT work? (was Re: A modest proposal (long))
Date: 
Message-ID: <38CF408C.2C179C7B@nokia.com>
thi wrote:

> "His Holiness the Reverend Doktor Xenophon Fenderson, the Carbon(d)ated" <········@irtnog.org> writes:
>
> > I confess I've never understood UNWIND-PROTECT.  Would someone explain
> > what it does, please?  Things like UNWIND-PROTECT (in Common Lisp) and
> > CALL/CC (in Scheme) have this aura of heavy wizardry surrounding them,
> > mostly because I've never understood how they work and for what one
> > would use them.
>
> could you explain your efforts to date at understanding these concepts?
> that might help people to see a path of explanation.

The simplest CL macro -->

(defmacro with-open-file ((file &rest a) &rest b)
  `(let ((,file (open ,@a)))
     (unwind-protect
  (progn ,@b)
       (close ,file))))

PKY


>
>
> thi
From: Tim Bradshaw
Subject: Re: How does UNWIND-PROTECT work? (was Re: A modest proposal (long))
Date: 
Message-ID: <ey3ln3m3wh3.fsf@cley.com>
* d  wrote:

> I confess I've never understood UNWIND-PROTECT.  Would someone explain
> what it does, please?  Things like UNWIND-PROTECT (in Common Lisp) and
> CALL/CC (in Scheme) have this aura of heavy wizardry surrounding them,
> mostly because I've never understood how they work and for what one
> would use them.

It lets you do something and then something else *even if the initial
something got an error*.  The classic example is things like making
sure open files get closed, or locks released, even if bad things have
happened.

--tim
From: Johan Kullstam
Subject: Re: How does UNWIND-PROTECT work? (was Re: A modest proposal (long))
Date: 
Message-ID: <m2n1o2w21t.fsf@euler.axel.nom>
"His Holiness the Reverend Doktor Xenophon Fenderson, the Carbon(d)ated" <········@irtnog.org> writes:

> >>>>> "EN" == Erik Naggum <····@naggum.no> writes:
> 
>     EN> (if [programmers] know about unwind-protect -- Kent Pitman has
>     EN> made the cogent argument that languages can be judged on the
>     EN> existence of such a language feature -- I'll argue that the
>     EN> same applies to programmers and whether they know about it).
> 
> I confess I've never understood UNWIND-PROTECT.  Would someone explain
> what it does, please?  Things like UNWIND-PROTECT (in Common Lisp) and
> CALL/CC (in Scheme) have this aura of heavy wizardry surrounding them,
> mostly because I've never understood how they work and for what one
> would use them.

consult the trusty lisp hyperspec
 
<URL:http://www.xanalys.com/software_tools/reference/HyperSpec/Body/speope_unwind-protect.html#unwind-protect>

i don't know the details of the machinery in the background of
unwind-protect but here is my take --

unwind-protect is good for making sure that you clean up after
yourself despite any errors or problems along the way.

the common example of using unwind-protect is with files.  file are
used thusly

1) you open a file.
2) you do stuff with the file.
3) you close the file.

but what happens if during step 2, the "do stuff with file" stage, a
disaster (ie a lisp error) or some other kind of abort happens?  well,
unwind-protect can make sure that you close the file anyway.

with-open-file is a macro which (besides opening the file) wraps up
your code with the unwind-protect, thus insuring you that the file
will get closed (as long as your whole lisp system doesn't collapse)
when you are done with it.

it's kind of like registering a hook.  you put the stuff that you want
done upon leaving a block into the clean-up section.  it's like a
progn-end-hook if that helps you think of it.

unwind-protect isn't all that mysterious, it's just a bookkeeping aid.
in a situation where you know you will need to clean up after
yourself, so you just schedule for that to happen in the future.

hope this helps.


i have no scheme experience and i never did grok call/cc the times it
was presented to me so i shall not attempt to explain that.

-- 
J o h a n  K u l l s t a m
[········@ne.mediaone.net]
Don't Fear the Penguin!
From: Joe Marshall
Subject: Re: How does UNWIND-PROTECT work? (was Re: A modest proposal (long))
Date: 
Message-ID: <uwvn5r3fl.fsf@alum.mit.edu>
 "His Holiness the Reverend Doktor Xenophon Fenderson, the Carbon(d)ated" <········@irtnog.org> writes:
 
 > >>>>> "EN" == Erik Naggum <····@naggum.no> writes:
 > 
 >     EN> (if [programmers] know about unwind-protect -- Kent Pitman has
 >     EN> made the cogent argument that languages can be judged on the
 >     EN> existence of such a language feature -- I'll argue that the
 >     EN> same applies to programmers and whether they know about it).
 > 
 > I confess I've never understood UNWIND-PROTECT.  Would someone explain
 > what it does, please?  Things like UNWIND-PROTECT (in Common Lisp) and
 > CALL/CC (in Scheme) have this aura of heavy wizardry surrounding them,
 > mostly because I've never understood how they work and for what one
 > would use them.
 
Example use:  You have a program that creates a file.  You want to
switch to a temporary directory before calling the program.  You can
do this:

(defun foo ()
  (cd "/tmp/")
  (run-program))

But when foo returns, you are now in the temporary directory.
You could do this:

(defun foo ()
  (let ((starting-directory (current-directory)))
    (cd "/tmp/")
    (let ((answer (run-program)))
      (cd starting-directory))))

And maybe even be a bit more clever because run-program may return
multiple values:

(defun foo ()
  (let ((starting-directory (current-directory)))
    (cd "/tmp/")
    (multiple-value-prog1 (run-program)
      (cd starting-directory))))

This will work, but you might notice that if you hit control-c
or throw out of (run-program), it doesn't set the directory back.
That's what unwind-protect is for.  You do this:

(defun foo ()
  (let ((starting-directory (current-directory)))
    (cd "/tmp/")
    (unwind-protect (run-program)
      (cd starting-directory))))

Now, when you exit (run-program) for *any reason*, normal return,
throw, control-c, whatever, before anything else happens, the code in
the cleanup form runs, and the current directory is restored to
its starting value.

There are a few subtleties:  If you have multiple pending
unwind-protects, they run in order from most recent to least recent.
If you CATCH, the unwind-protects prior to the CATCH won't be run
if you throw to the catch (it only unwinds to the level you are going
to, not the entire stack).  The protection form itself is *not*
protected, so if it errors or throws, all bets are off.  

That's how you use one.  Here's how it works:

Very well, if implemented correctly.

The usual implementation is put a marker on the stack for the
unwind protect.  When the protected form returns normally, the marker 
is popped and control transfers to the cleanup forms.

When a throw occurs, the stack is scanned for unwind-protects.  As
the throw happens, the stack is `unwound' to the level of each
intervening unwind-protect, control briefly resumes for the protection 
form, and when it returns, the throwing continues.

If you have a toy interpreter available, it is an amusing exercise to
implement unwind-protect for it.

--
~jrm
From: Christopher C Stacy
Subject: Re: How does UNWIND-PROTECT work? (was Re: A modest proposal (long))
Date: 
Message-ID: <x8lpuskrnlw.fsf@world.std.com>
You may wish to read Kent Pitman's paper comparing UNWIND-PROTECT with CALL/CC.
From: Tom Breton
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <m3snyaf6v7.fsf@world.std.com>
···@jpl.nasa.gov (Erann Gat) writes:

> In article <···············@cley.com>, Tim Bradshaw <···@cley.com> wrote:
> 
> > I think I agree with Erik about this.  There is clearly a problem here
> > in principle.  In practice I have *very* seldom been bitten by it, and
> > I'd be loth to change the language to make it `easier' for people at
> > the cost of adding something like the BIND macro you suggest (at
> > least, not with the syntax you suggest, which I have much the same
> > reaction to as Erik I'm afraid).  I'm also very loth to use up one of
> > the extremely small number of available characters to be a read-macro
> > for something like this.
> 
> I see I have not made myself clear.
> 
> The $ macro is optional.  

If it's optional, ISTM it doesn't solve the problem (such as the
problem is).  Using *...* is also optional.  So is using (declare
(special ...)) when it's not strictly needed.

> 
> Personally, I think:
> 
>    (bind x 1 $q 2 (values y z) (foo) (a $b c) (baz) in ...
> 
> is a win.  
[]

> I also wonder how many of you BIND haters are also LOOP haters.  I am
> really beginning to worry that people have lost sight of the fact that
> an S-expression with just one level of parens is still an S-expression.

Well, we have a real serious disagreement there.  I don't think you
have the feel for sexps.  Sticking parens around something may
technically make it a sexp, but it doesn't make it a tolerable one.  A
sexp should not have internal dependencies.  IMO even boa parameter
lists are iffy.

> > I'd also like to gratuitously point out that your technique doesn't
> > actually solve the whole problem: symbol-macros can mean that what
> > looks like an innocent variable is actually something entirely
> > different.
> 
> But symbol macros can only be established with lexical scope, so if
> there is a symbol macro it must be lexically manifested.  Global symbol
> macros would be truly problematic.  In fact, this is the problem with
> DEFVAR.  It essentially establishes a global symbol macro that replaces
> all occurrences of X with (symbol-value 'x), except that this happens
> silently, and there's no way to undo it.

Instead of all this, how about a system parameter that makes even
defvar require (declare (special ...)) or it's an error?

-- 
Tom Breton, http://world.std.com/~tob
Not using "gh" since 1997. http://world.std.com/~tob/ugh-free.html
From: Erann Gat
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <gat-0203001107080001@milo.jpl.nasa.gov>
In article <··············@world.std.com>, Tom Breton <···@world.std.com> wrote:


> > Personally, I think:
> > 
> >    (bind x 1 $q 2 (values y z) (foo) (a $b c) (baz) in ...
> > 
> > is a win.  
> []
> 
> > I also wonder how many of you BIND haters are also LOOP haters.  I am
> > really beginning to worry that people have lost sight of the fact that
> > an S-expression with just one level of parens is still an S-expression.
> 
> Well, we have a real serious disagreement there.  I don't think you
> have the feel for sexps.  Sticking parens around something may
> technically make it a sexp, but it doesn't make it a tolerable one.  A
> sexp should not have internal dependencies.  IMO even boa parameter
> lists are iffy.

I'm not sure what you mean by internal dependencies, but there is no
difference in spirit between my BIND and the standard LOOP.

(bind x = 1 and y = 2 in ...)

is exactly the same as

(loop for x = 1 and y = 2 return ...)

except for the particular choice of keywords.  (The only difference is
that in my BIND macro some of the keywords are optional whereas in LOOP
they are all required.)

E.
From: Pierre R. Mai
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <87wvnlqces.fsf@orion.dent.isdn.cs.tu-berlin.de>
···@jpl.nasa.gov (Erann Gat) writes:

> I'm not sure what you mean by internal dependencies, but there is no
> difference in spirit between my BIND and the standard LOOP.
> 
> (bind x = 1 and y = 2 in ...)
> 
> is exactly the same as
> 
> (loop for x = 1 and y = 2 return ...)
> 
> except for the particular choice of keywords.  (The only difference is
> that in my BIND macro some of the keywords are optional whereas in LOOP
> they are all required.)

I think a number of people are not very happy with LOOP syntax, as
opposed to LOOP functionality.  Given that LOOP had a considerable
history and usage before being adopted into the standard, that it
filled a non-trivial gap in Common Lisp functionality, and that it's
now "too late" anyway, we might as well make the best of it, and use
it where appropriate.  That doesn't mean we have to be happy about
introducing new constructs with the same defects:

- LOOP still breaks a lot of source (i.e. text) munging code, like
  indenting editors,
- LOOP keywords are not symbols  (i.e. the dispatching is done on
  symbol-names, not symbols, which is very bad, especially in light of 
  user-extensibility),
- Nesting of LOOP clauses can't be seen from automatic indentation,
- A number of constructs of CL had to be reinvented for LOOP (see
  conditional clauses, destructuring), because LOOP doesn't mesh well
  with the rest of CL.
- LOOP syntax is a mini Dylan/Pascal inside of CL.  Thus you have to
  switch between syntax styles while reading code.

Note that the above defects are defects only in the context of CL,
where they stand out as warts, because they run counter to the rest of
the CL environment.

Regs, Pierre.

-- 
Pierre Mai <····@acm.org>         PGP and GPG keys at your nearest Keyserver
  "One smaller motivation which, in part, stems from altruism is Microsoft-
   bashing." [Microsoft memo, see http://www.opensource.org/halloween1.html]
From: Tim Bradshaw
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <ey3n1ohezg7.fsf@cley.com>
* Pierre R Mai wrote:
> [...] Given that LOOP had a considerable
> history and usage before being adopted into the standard, [...]

This is a very significant reason for loop being a reasonable thing to
have -- large-scale experience with a closely-related system (probably
several).

--tim
From: Pierre R. Mai
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <87d7pcqq6p.fsf@orion.dent.isdn.cs.tu-berlin.de>
Tim Bradshaw <···@cley.com> writes:

> * Pierre R Mai wrote:
> > [...] Given that LOOP had a considerable
> > history and usage before being adopted into the standard, [...]
> 
> This is a very significant reason for loop being a reasonable thing to
> have -- large-scale experience with a closely-related system (probably
> several).

Indeed.

Regs, Pierre.

-- 
Pierre Mai <····@acm.org>         PGP and GPG keys at your nearest Keyserver
  "One smaller motivation which, in part, stems from altruism is Microsoft-
   bashing." [Microsoft memo, see http://www.opensource.org/halloween1.html]
From: Tom Breton
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <m3hfeoq3er.fsf@world.std.com>
···@jpl.nasa.gov (Erann Gat) writes:

> In article <··············@world.std.com>, Tom Breton <···@world.std.com> wrote:
> 
> 
> > Well, we have a real serious disagreement there.  I don't think you
> > have the feel for sexps.  Sticking parens around something may
> > technically make it a sexp, but it doesn't make it a tolerable one.  A
> > sexp should not have internal dependencies.  IMO even boa parameter
> > lists are iffy.
> 
> I'm not sure what you mean by internal dependencies, but there is no
> difference in spirit between my BIND and the standard LOOP.

Sorry, that is not a plus.

-- 
Tom Breton, http://world.std.com/~tob
Not using "gh" since 1997. http://world.std.com/~tob/ugh-free.html
From: Joe Marshall
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <ur9duzp2y.fsf@alum.mit.edu>
···@jpl.nasa.gov (Erann Gat) writes:

> Now, this has not been much of an issue because artificially separating
> the name spaces of lexical and dynamic variables using the *...* convention
> generally works to keep the problem at bay.  But the trouble is that this
> solution only works if you use it, and you can only use it if you are
> aware of it.  And even if you are aware of it, your collaborator might
> not be.  *You* might not have DEFVARed X, but how do you know that Joe
> didn't?

I didn't!  Honest!

> The solution to this problem is to change the language so that the
> distinction between dynamic and lexical bindings is locally manifested.

I agree that the distinction sohuld be locally manifest, but I don't
think we need a radical change to the language to ensure this.

A little help from the programming environment would go a long way to
solving the problem.  Wrapping '*' around a variable is the
de-facto standard for special variables.  If the compiler issued a
warning when you declared or used a special variable without '*', or
if you declared or used a non-special (lexical) variable _with_ a '*', 
it would probably solve the bulk of the problem without introducing
changes to the language. 

~jrm
From: Bob Pepin
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <86n1oetntm.fsf@homer.localnet>
Joe Marshall <·········@alum.mit.edu> writes:

> > The solution to this problem is to change the language so that the
> > distinction between dynamic and lexical bindings is locally manifested.
> 
> I agree that the distinction sohuld be locally manifest, but I don't
> think we need a radical change to the language to ensure this.
> 
> A little help from the programming environment would go a long way to
> solving the problem.  Wrapping '*' around a variable is the
> de-facto standard for special variables.  If the compiler issued a
> warning when you declared or used a special variable without '*', or
> if you declared or used a non-special (lexical) variable _with_ a '*', 
> it would probably solve the bulk of the problem without introducing
> changes to the language. 

(sorry if I got the terminology wrong, might be confusing name/variable, 
I don't know much about this stuff, just seemed to me like people were missing
something obvious)

Isn't the only real problem the overloading of let and that there is
no way for the compiler to know if you want to rebind the value of a
special variable or establish a new lexical variable? It seems to me
that the obvious solution would be to introduce a new construct
(fluid-let? I think that's what some schemes call it) that only
rebinds special variables so the compiler can issue a warning if there
was no preceding defvar of that variable. Could be trivially
implemented using a macro if there was a standard method to determine
if a variable was declared special. Wouldn't help with old code, but
wouldn't break it either, but offers the possibility of avoiding some
nasty bugs like the ones mentioned by the SBCL author earlier in the
future.

Nevermind if you already knew this and I just missed the point in all
the earlier messages, I'm kinda new to CL and programming (compared to
most people here..).

-- 
"Free software, free implementations, free sources, free to shoot
yourself if you cannot grasp it!" 
	-- Jerzy Karczmarczuk in comp.lang.functional
From: Dorai Sitaram
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <89tvor$jpn$1@news.gte.com>
In article <··············@homer.localnet>, Bob Pepin  <···@prophecy.lu> wrote:
>(sorry if I got the terminology wrong, might be confusing name/variable, 
>I don't know much about this stuff, just seemed to me like people were missing
>something obvious)
>
>Isn't the only real problem the overloading of let and that there is
>no way for the compiler to know if you want to rebind the value of a
>special variable or establish a new lexical variable? It seems to me
>that the obvious solution would be to introduce a new construct
>(fluid-let? I think that's what some schemes call it) that only
>rebinds special variables ... 

Fluid-let temporarily side-effects lexical variables,
but your point is a good one.  (I've always
mentally moved the stars from the variable onto the
Let.)

But the bigger question is: Why didn't CL adopt a
Fluid-let-like approach to begin with?  I'm sure there
are good reasons, but what are they?  Special
variables seem to make more sense for Scheme than for
CL, because they may help preserve tail-call
optimisation where Fluid-let (with its
resetting) simply cannot.  But this could not
have been a consideration with CL...

--d
From: Erann Gat
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <gat-0603001130330001@milo.jpl.nasa.gov>
In article <············@news.gte.com>, ····@goldshoe.gte.com (Dorai
Sitaram) wrote:

> But the bigger question is: Why didn't CL adopt a
> Fluid-let-like approach to begin with?  I'm sure there
> are good reasons, but what are they?  Special
> variables seem to make more sense for Scheme than for
> CL, because they may help preserve tail-call
> optimisation where Fluid-let (with its
> resetting) simply cannot.  But this could not
> have been a consideration with CL...

I believe that the reason things are the way they are is that CL
was trying to unify many disparate dialects of Lisp.  Some of these
dialects were dynamically scoped by default, so they had to come up
with a strategy that would allow code written for dynamic-binding-by-
default Lisps to continue to work with minimal modifications, and
DEFVAR was what they came up with. Not a bad solution under the
circumstances.

Erann Gat
···@jpl.nasa.gov
From: Dorai Sitaram
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <8a1d78$m3m$1@news.gte.com>
Erann Gat wrote:
>
>I believe that the reason things are the way they are is that CL
>was trying to unify many disparate dialects of Lisp.  Some of these
>dialects were dynamically scoped by default, so they had to come up
>with a strategy that would allow code written for dynamic-binding-by-
>default Lisps to continue to work with minimal modifications, and
>DEFVAR was what they came up with. Not a bad solution under the
>circumstances.


OK.   But legacy considerations don't explain why
global lexical variables needed to be eliminated to
"make way" (as it seems in retrospect) for special
variables.  These could have coexisted fine it seems
to me.  A defglobal alongside defvar.

--d
From: Harley Davis
Subject: Re: A modest proposal (long)
Date: 
Message-ID: <38c56f21$0$239@newsreader.alink.net>
Dorai Sitaram <····@goldshoe.gte.com> wrote in message
·················@news.gte.com...
> Erann Gat wrote:
> >
> >I believe that the reason things are the way they are is that CL
> >was trying to unify many disparate dialects of Lisp.  Some of these
> >dialects were dynamically scoped by default, so they had to come up
> >with a strategy that would allow code written for dynamic-binding-by-
> >default Lisps to continue to work with minimal modifications, and
> >DEFVAR was what they came up with. Not a bad solution under the
> >circumstances.
>
>
> OK.   But legacy considerations don't explain why
> global lexical variables needed to be eliminated to
> "make way" (as it seems in retrospect) for special
> variables.  These could have coexisted fine it seems
> to me.  A defglobal alongside defvar.

ISLisp specifies dynamic-let (for binding) and dynamic (for access) special
forms.  I forget what the definer for global special vars is - either
defdynamic or defvar.  We also had these forms in ILOG Talk and EuLisp and I
found using a separate namespace for special vars to be clearer than CL's
mechanism of mixing namespaces and using declarations to disambiguate.

-- Harley