Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

beginner question

20 views
Skip to first unread message

Adam Lasser

unread,
Apr 23, 1998, 3:00:00 AM4/23/98
to

Hi there. I will apologize in advance for a stupid question. I am
having a problem with undefined variables. When I compile my program, I
get errors about variables being undefined. I am using the special form
setq to assign the variables a value. Am I doing something wrong?
Please help.

Thanks.

adam lasser


Thomas A. Russ

unread,
Apr 23, 1998, 3:00:00 AM4/23/98
to

Adam Lasser <las...@csst.cs.technion.ac.il> writes:

There are a couple potential things that are being left out.

I presume that the compiler is complaining because some variables were
undefined and they are being assumed to be "special". The solutions
vary depending on your particular needs.

First, you might try to decide if you really need to be using setq at
all. Often in Lisp you can write an awful lot of code that doesn't
require explicitly setting variables using setq. Often when programmers
come to Lisp from other languages they tend to write a lot more setq
forms than experienced lisp programmers, who generally prefer to nest
expressions rather than introduce extra variables.

Second, it would be worth investigating whether you should introduce
local bindings for the variables using LET and its cousins. This
produces a local, lexically scoped variables that you can then modify
using setq.

Third, if you really need to have global values, then you should tell
the compiler that you intend the variables to be globally visible and
have dynamic scope by using a DEFVAR or DEFPARMETER declaration in your
code.

--
Thomas A. Russ, USC/Information Sciences Institute t...@isi.edu

Kelly Murray

unread,
Apr 23, 1998, 3:00:00 AM4/23/98
to

> In Common Lisp, how do you define a global variable that's *not* dynamic,
> that is, that has lexical scope? In Scheme, of course, all variables are

It's missing from CL. With a true multiprocessor lisp, it's really
needed to avoid doing a slow special-variable lookup when you
know the variable is a global. I added (defglobal xx) to my old MP Lisp.

You could sort-of fake it using symbol-macros and a function call, e.g.

(defun get-global-value (nth) (aref '#("foo") nth))

(define-symbol-macro lexical-foo (get-global-value 0))

(defun testit ()
(list lexical-foo (let ((lexical-foo "localfoo")) lexical-foo))
)

(testit) ==> ("foo" "localfoo")


-Kelly Murray k...@franz.com


Rob Warnock

unread,
Apr 24, 1998, 3:00:00 AM4/24/98
to

Thomas A. Russ <t...@sevak.isi.edu> replied (to Adam Lasser):
+---------------

| Third, if you really need to have global values, then you should tell
| the compiler that you intend the variables to be globally visible and
| have dynamic scope by using a DEFVAR or DEFPARMETER declaration in your
| code.
+---------------

That brings up a stupid-beginner-question of *mine*...

In Common Lisp, how do you define a global variable that's *not* dynamic,
that is, that has lexical scope? In Scheme, of course, all variables are

lexical (unless one has done some hackery with dynamic-wind), so this is
simply:

(define line-counter 0)

and then if you later do something like:

(define bar (lambda () (display line-counter) (newline)))

(define foo (lambda (...)
...
(let loop ((line-counter 47))
...
(bar)
...
(loop (+ line-counter 1)))
...))

the new definition of "line-counter" lexically shadows the global one
*within* "foo", but the call to "bar" uses the global version.

But if I understand your comment about DEFVAR & DEFPARMETER implying
dynamic scope (which agrees with my reading of CLtLx & CLHS), then
in CL "bar" would see the current *dynamic* value of "line-counter",
that is, the value established by the "let" in "foo".

How does one avoid this when one wants normal (to a Scheme user)
lexical scope for a global variable? What declaration or initial
definition form does one use?


-Rob

-----
Rob Warnock, 7L-551 rp...@sgi.com http://reality.sgi.com/rpw3/
Silicon Graphics, Inc. Phone: 650-933-1673 [New area code!]
2011 N. Shoreline Blvd. FAX: 650-933-4392
Mountain View, CA 94043 PP-ASEL-IA

Barry Margolin

unread,
Apr 24, 1998, 3:00:00 AM4/24/98
to

In article <6hp3jt$4t...@fido.asd.sgi.com>,

Rob Warnock <rp...@rigden.engr.sgi.com> wrote:
>That brings up a stupid-beginner-question of *mine*...
>
>In Common Lisp, how do you define a global variable that's *not* dynamic,
>that is, that has lexical scope?

You can't. We talked about adding something like a LEXICAL declaration,
but it never made it in. Kent can probably remember more of the details.

--
Barry Margolin, bar...@bbnplanet.com
GTE Internetworking, Powered by BBN, Cambridge, MA
*** DON'T SEND TECHNICAL QUESTIONS DIRECTLY TO ME, post them to newsgroups.

Erik Naggum

unread,
Apr 24, 1998, 3:00:00 AM4/24/98
to

* Rob Warnock

| That brings up a stupid-beginner-question of *mine*...

I had the same question a few years ago, related to what SETQ at
top-level would do to an undeclared symbol: CMUCL automatically declares
it special, Allegro CL does not, so I thought there was something to a
non-special global myself. as it turns out, that's just an ordinary
symbol, but that is mainly an artifact of the top-level loop. I'm not
sure I _fully_ understand Barry's and Kelly's responses, though.

| In Common Lisp, how do you define a global variable that's *not* dynamic,
| that is, that has lexical scope?

you don't, but there is nothing to bar you from accessing a symbol's
slots directly, such as with SYMBOL-VALUE. since the compiler will barf
on references to undeclared symbols, you need to access them explicitly
with (SYMBOL-VALUE 'SYMBOL) and (SETF (SYMBOL-VALUE 'SYMBOL)). this is
not pretty, and might even be seen as thwarting the semantics of the
language.

| How does one avoid this when one wants normal (to a Scheme user) lexical
| scope for a global variable? What declaration or initial definition form
| does one use?

well, in sharp contrast to Scheme, we have very easy access to lexical
closures in Common Lisp. e.g.,

(let ((line-counter 0))
(defun foo (...)
... line-counter ...)
(defun bar (...)
... line-counter ...))

will create two functions FOO and BAR that share the lexical binding of
LINE-COUNTER. in Scheme, as I'm sure you are aware, the LET-form would
remove the top-level-ness of the now _internal_ defining forms and just
return some arbitrary values instead of defining new functions. in this
regard, I find Common Lisp to be far superior to Scheme, which encourages
a proliferation of global symbols with lexical semantics as opposed to
carefully constrained access to shared lexical bindings, which I found
real cumbersome to do last time I tried it in Scheme, but I'm certainly
no fan of Scheme, so I might well have missed something important.

#:Erik
--
Abort, Retry, or Upgrade?

Dorai Sitaram

unread,
Apr 24, 1998, 3:00:00 AM4/24/98
to

In article <31023979...@naggum.no>, Erik Naggum <cle...@naggum.no> wrote:
>* Rob Warnock

>| How does one avoid this when one wants normal (to a Scheme user) lexical
>| scope for a global variable? What declaration or initial definition form
>| does one use?
>
> well, in sharp contrast to Scheme, we have very easy access to lexical
> closures in Common Lisp. e.g.,
>
>(let ((line-counter 0))
> (defun foo (...)
> ... line-counter ...)
> (defun bar (...)
> ... line-counter ...))
>
> will create two functions FOO and BAR that share the lexical binding of
> LINE-COUNTER. in Scheme, as I'm sure you are aware, the LET-form would
> remove the top-level-ness of the now _internal_ defining forms and just
> return some arbitrary values instead of defining new functions. in this
> regard, I find Common Lisp to be far superior to Scheme, which encourages
> a proliferation of global symbols with lexical semantics as opposed to
> carefully constrained access to shared lexical bindings, which I found
> real cumbersome to do last time I tried it in Scheme, but I'm certainly
> no fan of Scheme, so I might well have missed something important.

Scheme does let you do

(define foo #f)
(define bar #f)

(let ((line-counter 0))
(set! foo (lambda ... use line-counter ...))
(set! bar (lambda ... use line-counter ...)))

foo and bar are globally visible procedures and line-counter
is a lexical variable visible only to the foo and bar
procedures. There is no necessity or even encouragement
that line-counter be global.

Perhaps the cumbersomeness lies in the stopgap
initialization of foo and bar to #f, an arbitrary value.
Some Schemes mitigate this somewhat by allowing

(define foo)
(define bar)

the assumption being that foo and bar will get initialized
later (within or without a lexical contour).

--d


Marc Wachowitz

unread,
Apr 24, 1998, 3:00:00 AM4/24/98
to

Erik Naggum <cle...@naggum.no> wrote:
> [...] since the compiler will barf

> on references to undeclared symbols, you need to access them explicitly
> with (SYMBOL-VALUE 'SYMBOL) and (SETF (SYMBOL-VALUE 'SYMBOL)). this is
> not pretty, and might even be seen as thwarting the semantics of the
> language.

I think the following works in a conforming Common Lisp implementation:

(defmacro defglobal (name &optional init)
;; documentation string support omitted for brevity
(let ((place (make-symbol (symbol-string name))))
`(progn
(define-symbol-macro ,name (symbol-value ',place))
(setq ,name ,init))))

I didn't test this, since CMU-CL (at least the version which I have now)
unfortunately doesn't implement DEFINE-SYMBOL-MACRO.

I suggest uninterned symbols, named just like the intended lexical global
variable, to increase readability in macro expansion and debugging output.
Of course, different forms of storage are possible. Note that one needs
to do something more complicated if DEFGLOBAL forms are meant to work
reasonably well when they are reloaded, without reloading everything
depending on them, e.g. in compiled functions referencing the previously
created uninterned symbol. For example, one could store such uninterned
symbols in some hash table accessed via the argument to DEFGLOBAL (which
is probably an ordinary symbol with a proper package, though that's not
required), and reuse the previously created uninterned symbol whenever a
DEFGLOBAL is repeated for the same symbol. Of course, this hash table
would then be made to survive reloading its definition (using DEFVAR or
an explicit SYMBOL-VALUE for an interned symbol, checking pre-existence).
This hash table would only be used when DEFGLOBAL is evaluated; variable
access would still go directly to the uninterned symbol, which is known
at symbol-macro expansion time. One should also support an optional type
declaration form in DEFGLOBAL calls, which would then wrap a THE form
around the expansion of the symbol-macro (ordinary declaration for such
"global variables" aren't possible).

I guess that's as close as one can come in Common Lisp to a true lexical
global variable. It's not very elegant, but once the machinery is defined,
usage should be relatively simple and work without horrible surprises.

-- Marc Wachowitz <m...@ipx2.rz.uni-mannheim.de>

Kent M Pitman

unread,
Apr 24, 1998, 3:00:00 AM4/24/98
to

m...@ipx2.rz.uni-mannheim.de (Marc Wachowitz) writes:

> I think the following works in a conforming Common Lisp implementation:
>
> (defmacro defglobal (name &optional init)
> ;; documentation string support omitted for brevity
> (let ((place (make-symbol (symbol-string name))))
> `(progn
> (define-symbol-macro ,name (symbol-value ',place))
> (setq ,name ,init))))
>
> I didn't test this, since CMU-CL (at least the version which I have now)
> unfortunately doesn't implement DEFINE-SYMBOL-MACRO.

I don't think it will work, but not for the reasons you probably think
you checked. Code that is externalized into a file is allowed to "split"
a gensym. (symbol-value '<gensym>) will therefore not necessarily access
the same gensym in all cases (particularly, if references occur in two
different compiled files).

I think something like the following will work better:

(defmacro defglobal (name &optional init)

`(progn
(define-symbol-macro ,name
(cdr (load-time-value (global-value-cell ',name))))
(setq ,name ,init)
',name)) ;return the name, not its value

(defun global-value-cell (name)
(or (get name 'global-value-cell)
(setf (get name 'global-value-cell)
(cons name ;for self-documentation
nil))))

> I guess that's as close as one can come in Common Lisp to a true lexical
> global variable. It's not very elegant, but once the machinery is defined,
> usage should be relatively simple and work without horrible surprises.

FWIW, DEFINE-SYMBOL-MACRO was added to Common Lisp exactly for cross-language
compatibility because it's useful in defining global lexicals and also
global constants [that can't be setq'd but can be bound], which occur in
other dialects of Lisp (particularly ISLISP, the ISO Lisp Standard).

Rob Warnock

unread,
Apr 28, 1998, 3:00:00 AM4/28/98
to

Erik Naggum <cle...@naggum.no> wrote:
+---------------

| | How does one avoid this when one wants normal (to a Scheme user) lexical
| | scope for a global variable? What declaration or initial definition form
| | does one use?
|
| well, in sharp contrast to Scheme, we have very easy access to lexical
| closures in Common Lisp. e.g.,
|
| (let ((line-counter 0))
| (defun foo (...)
| ... line-counter ...)
| (defun bar (...)
| ... line-counter ...))
|
| will create two functions FOO and BAR that share the lexical binding of
| LINE-COUNTER. in Scheme, as I'm sure you are aware, the LET-form would
| remove the top-level-ness of the now _internal_ defining forms and just
| return some arbitrary values instead of defining new functions.
+---------------

But that really wasn't the quesion I was asking! To rephrase it in the
context of your example, suppose when you write the code you give, there's
*already* a top-level variable named "line-counter" -- which, as several
people have answered me, is necessarily "special" (dynamic). So now instead
of getting a new lexical variable "line-counter" for your functions "foo" &
"bar" to share privately, you have perturbed the value of the global dynamic
variable "line-counter", and if either "foo" or "bar" calls a function that
uses "line-counter", unexpectedness will happen... (Won't it?)

+---------------


| I find Common Lisp to be far superior to Scheme, which encourages
| a proliferation of global symbols with lexical semantics as opposed to
| carefully constrained access to shared lexical bindings, which I found
| real cumbersome to do last time I tried it in Scheme, but I'm certainly
| no fan of Scheme, so I might well have missed something important.

+---------------

As someone else pointed out, the way you do what you want in Scheme is:

(define foo #f)
(define bar #f)
(let ((line-counter 0))

(set! foo (lambda (...) ...))
(set! bar (lambda (...) ...)))

(which is basically identical to the usual expansion of "letrec"...)

Thus, one *can* carefully control which symbols one pollutes the global
namespace with. (Of course, I concede you the point that one *needs* to
take such care, since standard Scheme only has one namespace.)

Erik Naggum

unread,
Apr 28, 1998, 3:00:00 AM4/28/98
to

* Rob Warnock

| But that really wasn't the quesion I was asking! To rephrase it in the
| context of your example, suppose when you write the code you give, there's
| *already* a top-level variable named "line-counter" -- which, as several
| people have answered me, is necessarily "special" (dynamic). So now instead
| of getting a new lexical variable "line-counter" for your functions "foo" &
| "bar" to share privately, you have perturbed the value of the global dynamic
| variable "line-counter", and if either "foo" or "bar" calls a function that
| uses "line-counter", unexpectedness will happen... (Won't it?)

if you don't stick to the very good convention to use asterisks around
special variables, the expected unexpectedness will happen. that's why
you _always_ want to use asterisks around special variables. there is no
(declare (nospecial ...)), unfortunately. (I think there should be.)

| As someone else pointed out, the way you do what you want in Scheme is:
|
| (define foo #f)
| (define bar #f)
| (let ((line-counter 0))
| (set! foo (lambda (...) ...))
| (set! bar (lambda (...) ...)))
|
| (which is basically identical to the usual expansion of "letrec"...)

let's see some elegant syntax for it, now that you have DEFINE-SYNTAX to
play with, and I'll perhaps modify my statement. the above (the use of
internal vs top-level DEFINE in general, actually) is such a horribly
klutzy way of doing things that my knee-jerk reaction is "inelegant by
design". Schemers don't think so -- they have already decided that
Scheme is elegant, and that this is "necessary", although they keep
arguing that "necessary" translates to "inelegant" in Common Lisp. I
find it moderately amusing to tease Schemers with instances like this.

Steve Gonedes

unread,
Apr 28, 1998, 3:00:00 AM4/28/98
to


rp...@rigden.engr.sgi.com (Rob Warnock) writes:

<
< Erik Naggum <cle...@naggum.no> wrote:
< +---------------
< | | How does one avoid this when one wants normal (to a Scheme user) lexical
< | | scope for a global variable? What declaration or initial definition form
< | | does one use?
< |
< | well, in sharp contrast to Scheme, we have very easy access to lexical
< | closures in Common Lisp. e.g.,


I'm not really sure I understand, but maybe this is what you mean.

(defvar *counter* 0)


(defun that-thing (num)
(expt num *counter*))

(defun this-thing (num)
(let ((*counter* *counter*)) ;***
(incf *counter* 2)
(that-thing num)))


(this-thing 2) => 4
*counter* => 0

Dunno, I usually bind the global variable with a new value in a let
(actually I usually leave them alone but).

Closures are very easy in common-lisp as well, continuations can be
tricky, but as long as you have closures all is well.

If you think about it let is like a closure. (From Grahms book).

(defmacro our-let (binds &body form)
`((lambda ,(mapcar #'(lambda (x)
(if (consp x) (car x) x))
binds)
,@form)
,@(mapcar #'(lambda (x)
(if (consp x) (cadr x) nil))
binds)))

(macroexpand '(our-let ((a 1) (b 2)) (list a b)))
=> ((LAMBDA (A B) (LIST A B)) 1 2)

Kinda neat I think.

Sunil Mishra

unread,
Apr 29, 1998, 3:00:00 AM4/29/98
to

In article <6i5mck$3...@bgtnsc02.worldnet.att.net> Steve Gonedes <jgon...@worldnet.att.net> writes:

I'm not really sure I understand, but maybe this is what you mean.

(defvar *counter* 0)


(defun that-thing (num)
(expt num *counter*))

(defun this-thing (num)
(let ((*counter* *counter*)) ;***
(incf *counter* 2)
(that-thing num)))


(this-thing 2) => 4
*counter* => 0

Dunno, I usually bind the global variable with a new value in a let
(actually I usually leave them alone but).

As I interpreted the question that had originally been asked, the issue was
using global variables such that they have lexical scope, rather than
dynamic. What you have there is still a dynamic binding, since the effects
of rebinding *counter* spread outside the lexical scope of the let binding.

If *counter* had been lexically bound, the result of that computation would
have been (expt 2 0) = 1.

What I can't figure out is *why* I would want a global variable with
lexical binding. In the above example at least, if I wanted a lexical
version of the global variable, I would have simply bound *counter* to a
different variable. Is there any situation where the lexical scope of a
variable is not immediately determinate? That is the only situation where I
can imagine using such a facility.

Sunil

Dorai Sitaram

unread,
Apr 29, 1998, 3:00:00 AM4/29/98
to

In article <efyhg3c...@cleon.cc.gatech.edu>,

Sunil Mishra <smi...@cleon.cc.gatech.edu> wrote:
>
>What I can't figure out is *why* I would want a global variable with
>lexical binding. In the above example at least, if I wanted a lexical
>version of the global variable, I would have simply bound *counter* to a
>different variable. Is there any situation where the lexical scope of a
>variable is not immediately determinate? That is the only situation where I
>can imagine using such a facility.

It isn't so much that people would want to lexically shadow
global variables. It's more that they could be using
genuinely local lexical variables with all the good
intentions, and all it takes to ruin it all is for
themselves or someone else to inadvertently slip in a global
variable with the same name.

The *...* convention helps somewhat. It just seems a bit
incongruous to some people that one needs an arbitrary
naming convention, especially in a language with multiple
namespaces, to keep global and local variables from stomping
on each other.

That said, I'm sure there is a good reason why this
inconvenience is acceptable. I haven't figured it out yet.

--d


Lyman S. Taylor

unread,
Apr 29, 1998, 3:00:00 AM4/29/98
to
>In article <6i5mck$3...@bgtnsc02.worldnet.att.net> Steve Gonedes <jgon...@worldnet.att.net> writes:


> (defun this-thing (num)
> (let ((*counter* *counter*)) ;***

(declare (special *counter*)) ; not really needed but makes the
; ramifications explicit.

> (incf *counter* 2)
> (that-thing num)))

>If *counter* had been lexically bound, the result of that computation would


>have been (expt 2 0) = 1.

That's why the "special" declaration would help those from purely
lexical backgrounds not fall into this dynamic scoping trap here.

>What I can't figure out is *why* I would want a global variable with
>lexical binding.

If you do not follow the convention of labelling your globals with
"stars on both sides", *<name>*, then there is a possibility that one
might reuse a global identifier name in a context where only local
ramifications were intended. If one used one of the standard constructs
of declaring a global you get dynamic scoping characteristics.

(defvar notlocal "Global Val" )

(defun foo () notlocal )

(defun bar (notlocal ) (foo) )

? (foo )
"Global Val"
? (bar "Eh????" )
"Eh????"

There isn't any special syntatic/semantic "magic" associated with
*<name>* enforced in the language itself. So if they don't use it
for globals and someone happens to use what they might think is a
local... you have a name collision problem.

You could have a lexical global... (but you can "change the rules"...)

? (setq lex-global "Global var" )
"Global var"
? (defun fooo () lex-global)
FOOO
? (fooo )
"Global var"
? (defun barr ( lex-global) (fooo))
BARR
? (barr "Ehh??")
"Global var"
? (defun barr2 ( lex-global) (declare (special lex-global)) (fooo))
BARR2
? (barr2 "Ehh??")
"Ehh??"

I also think there is some performance overhead in dealing with dynmically
scoped var's lookup.

--
Lyman S. Taylor Comment by a professor observing two students
(ly...@cc.gatech.edu) unconscious at their keyboards:
"That's the trouble with graduate students.
Every couple of days, they fall asleep."

Jeff Dalton

unread,
Apr 29, 1998, 3:00:00 AM4/29/98
to

Erik Naggum <cle...@naggum.no> writes:

> you don't, but there is nothing to bar you from accessing a symbol's

> slots directly, such as with SYMBOL-VALUE. since the compiler will barf


> on references to undeclared symbols, you need to access them explicitly
> with (SYMBOL-VALUE 'SYMBOL) and (SETF (SYMBOL-VALUE 'SYMBOL)). this is
> not pretty, and might even be seen as thwarting the semantics of the
> language.

You should also be able to do

(locally (declare (special x)) x)

and

(locally (declare (special x)) (setq x y))

(Of course, the details can be hidden by macros.)

-- jeff

Vassil Nikolov

unread,
Apr 29, 1998, 3:00:00 AM4/29/98
to

On Tue, 28 Apr 1998 02:42:07 -0700,
Erik Naggum <cle...@naggum.no> wrote:

>* Rob Warnock
>| But that really wasn't the quesion I was asking! To rephrase it in the
>| context of your example, suppose when you write the code you give, there's
>| *already* a top-level variable named "line-counter" -- which, as several
>| people have answered me, is necessarily "special" (dynamic). So now instead
>| of getting a new lexical variable "line-counter" for your functions "foo" &
>| "bar" to share privately, you have perturbed the value of the global dynamic
>| variable "line-counter", and if either "foo" or "bar" calls a function that
>| uses "line-counter", unexpectedness will happen... (Won't it?)
>
> if you don't stick to the very good convention to use asterisks around
> special variables, the expected unexpectedness will happen. that's why
> you _always_ want to use asterisks around special variables. there is no
> (declare (nospecial ...)), unfortunately. (I think there should be.)

Right; unfortunately, there is no way to enforce this good convention
(I have seen at least one Common Lisp program where it was _not_ followed;
and the author wasn't just a random losing programmer). I quite agree
that having such a declaration would be nice (perhaps `noTspecial' like
`notinline'?), and there are some even more radical approaches; maybe
a future revision of the standard will bring some development in that
direction. In the meantime, there is a little bit of defensive
programming that could make you sleep better, using SYMBOL-MACROLET
to introduce a dummy symbol-macrodefinition for the symbol that
names the local variable that must not be special (since the compiler
catches it as an error if a dynamic variable is defined in such
a way). This looks less ugly if wrapped up in a macro, e.g.

(let ((x 0))
;; force a compile-time error if x is declared special
(compiler-assert-local x) ;expands into a nested symbol-macrolet
...)

If we had DECLARATION-INFORMATION, then we would have more options.

Best regards,
Vassil.


Rob Warnock

unread,
Apr 30, 1998, 3:00:00 AM4/30/98
to

Erik Naggum <cle...@naggum.no> wrote:
+---------------
| if you don't stick to the very good convention to use asterisks around
| special variables, the expected unexpectedness will happen. that's why
| you _always_ want to use asterisks around special variables.
+---------------

Aha! That explains why more than one Scheme expert has bitched at
me when I put asterisks around my global variables in Scheme code.
I was assuming the asterisk convention meant "global" -- I see
now it means "special". (And of course, there *isn't* any "special"
variable type in Scheme, though you can get much of the same effect
with "fluid-let", for those Schemes that have that.)

+---------------


| there is no (declare (nospecial ...)), unfortunately.
| (I think there should be.)

+---------------

Me, too.

Anyway, thanks, everyone, for clearing that up.
(My question turned out not to be quite as dumb
as I feared it might be.)

Rob Warnock

unread,
Apr 30, 1998, 3:00:00 AM4/30/98
to

Lyman S. Taylor <ly...@cc.gatech.edu> wrote:
+---------------

| Sunil Mishra <smi...@cleon.cc.gatech.edu> wrote:
| >What I can't figure out is *why* I would want a global variable with
| >lexical binding.
|
| If you do not follow the convention of labelling your globals with
| "stars on both sides", *<name>*, then there is a possibility that one
| might reuse a global identifier name in a context where only local
| ramifications were intended.
+---------------

Actually, I would now claim that the proper convention is to label
not "global" but *special* variables with asterisks (which in CL
just so happen to be all globals, but this is not true in Scheme).

0 new messages