From: Robert Maas, http://tinyurl.com/uh3t
Subject: Any programmable way to ask whether a symbol has been proclaimed special?
Date: 
Message-ID: <rem-2008may11-005@yahoo.com>
Today I got in a situation where I thought I had declared a
particular symbol to be special, by means of DEFVAR most likely,
but was getting strange behaviour related to it. I wanted to
diagnose the problem by first learning whether the symbol had been
proclaimed special or not. I first looked on the property list of
that symbol, but there was nothing there at all, no SPECIAL flag or
anything like that. I then spent a half hour searching through
CLtL1 without finding any predicate that tells whether a symbol is
special (already) or not. I checked the HyperSpec and couldn't find
any such predicate there either. Then suddenly I remembered
DESCRIBE, which printed out among other things:
  It is a special variable; no current value.
OK, so I should have thought of that first. But there's no SPECIALP
predicate or anything else I can find. How does DESCRIBE know that
the symbol is special? How does the JIT compiler built into the
REP loop know that it's special when it's deciding whether to do
lexical or special bindings? If I ever want to automate the
checking of several symbols to see if I forgot to proclaim any of
them special, how can I do that, except by binding standard output
to a string-output-string and calling DESCRIBE in that context and
then parsing the resultant string of output from DESCRIBE??

This is in CMUCL, if it makes any difference. I'm hoping for some
ANSI-CL function (predicate) rather than a CMUCL-specific function
(predicate), but I'm curious in any case.

From: Kent M Pitman
Subject: Re: Any programmable way to ask whether a symbol has been proclaimed special?
Date: 
Message-ID: <uskwokpsi.fsf@nhplace.com>
···················@SpamGourmet.Com (Robert Maas, http://tinyurl.com/uh3t) writes:

> Today I got in a situation where I thought I had declared a
> particular symbol to be special, by means of DEFVAR most likely,
> but was getting strange behaviour related to it. I wanted to
> diagnose the problem by first learning whether the symbol had been
> proclaimed special or not. I first looked on the property list of
> that symbol, but there was nothing there at all, no SPECIAL flag or
> anything like that. I then spent a half hour searching through
> CLtL1 without finding any predicate that tells whether a symbol is
> special (already) or not. I checked the HyperSpec and couldn't find
> any such predicate there either. Then suddenly I remembered
> DESCRIBE, which printed out among other things:
>   It is a special variable; no current value.
> OK, so I should have thought of that first. But there's no SPECIALP
> predicate or anything else I can find. How does DESCRIBE know that
> the symbol is special? How does the JIT compiler built into the
> REP loop know that it's special when it's deciding whether to do
> lexical or special bindings? If I ever want to automate the
> checking of several symbols to see if I forgot to proclaim any of
> them special, how can I do that, except by binding standard output
> to a string-output-string and calling DESCRIBE in that context and
> then parsing the resultant string of output from DESCRIBE??
> 
> This is in CMUCL, if it makes any difference. I'm hoping for some
> ANSI-CL function (predicate) rather than a CMUCL-specific function
> (predicate), but I'm curious in any case.

I don't think there's a built-in predicate.  I suspect the following
is portable, though obviously it calls EVAL so doesn't work so well
if you want to dump out an application that has tree-shaken the 
evaluator and compiler out of your Lisp...

(defun pervasively-special-p (var)
  (values
    (ignore-errors ;in case binding a constant doesn't work
      (eval `(let ((,var nil))
               (declare (special ,var))
               (let ((,var t))
                 (symbol-value ',var)))))))

(Also, it has a tiny timing window during which if you interrupted the
process doing that, the given special variable might have a bogus
value.)

Examples:
 (pervasively-special-p 'x) => NIL
 (pervasively-special-p '*print-base*) => T

Note that in the latter case, *PRINT-BASE* is momentarily bound to T,
so there is a tiny time window during which if you were to interrupt
that process you could be in a bad state.  But SYMBOL-VALUE is
generally fast and generally doesn't use any special variable state,
so that might be ok for you... :)

At least it gives you a fallback implementation for those
implementations that don't have something better to offer.
From: Chris Barts
Subject: Re: Any programmable way to ask whether a symbol has been proclaimed special?
Date: 
Message-ID: <87d4nrqf0y.fsf@chbarts.motzarella.org>
Kent M Pitman <······@nhplace.com> writes:

> ···················@SpamGourmet.Com (Robert Maas, http://tinyurl.com/uh3t) writes:
>
>> Today I got in a situation where I thought I had declared a
>> particular symbol to be special, by means of DEFVAR most likely,
>> but was getting strange behaviour related to it. I wanted to
>> diagnose the problem by first learning whether the symbol had been
>> proclaimed special or not. I first looked on the property list of
>> that symbol, but there was nothing there at all, no SPECIAL flag or
>> anything like that. I then spent a half hour searching through
>> CLtL1 without finding any predicate that tells whether a symbol is
>> special (already) or not. I checked the HyperSpec and couldn't find
>> any such predicate there either. Then suddenly I remembered
>> DESCRIBE, which printed out among other things:
>>   It is a special variable; no current value.
>> OK, so I should have thought of that first. But there's no SPECIALP
>> predicate or anything else I can find. How does DESCRIBE know that
>> the symbol is special? How does the JIT compiler built into the
>> REP loop know that it's special when it's deciding whether to do
>> lexical or special bindings? If I ever want to automate the
>> checking of several symbols to see if I forgot to proclaim any of
>> them special, how can I do that, except by binding standard output
>> to a string-output-string and calling DESCRIBE in that context and
>> then parsing the resultant string of output from DESCRIBE??
>> 
>> This is in CMUCL, if it makes any difference. I'm hoping for some
>> ANSI-CL function (predicate) rather than a CMUCL-specific function
>> (predicate), but I'm curious in any case.
>
> I don't think there's a built-in predicate.  I suspect the following
> is portable, though obviously it calls EVAL so doesn't work so well
> if you want to dump out an application that has tree-shaken the 
> evaluator and compiler out of your Lisp...
>
> (defun pervasively-special-p (var)
>   (values
>     (ignore-errors ;in case binding a constant doesn't work
>       (eval `(let ((,var nil))
>                (declare (special ,var))
>                (let ((,var t))
>                  (symbol-value ',var)))))))
>
> (Also, it has a tiny timing window during which if you interrupted the
> process doing that, the given special variable might have a bogus
> value.)

Would this bug likely be tickled on a multithreaded Lisp?

>
> Examples:
>  (pervasively-special-p 'x) => NIL
>  (pervasively-special-p '*print-base*) => T

Except this fails on SBCL:

{begin transcript:
CL-USER> (pervasively-special-p '*print-base*)
; in: LAMBDA NIL
;     LET
; 
; caught WARNING:
;   Compile-time package lock violation:
;     Lock on package COMMON-LISP violated when declaring *PRINT-BASE* special.
;   See also:
;     The SBCL Manual, Node "Package Locks"
;     The ANSI Standard, Section 11.1.2.1.2
; 
; caught ERROR:
;   Lock on package COMMON-LISP violated when declaring *PRINT-BASE* special.
;   See also:
;     The SBCL Manual, Node "Package Locks"
;     The ANSI Standard, Section 11.1.2.1.2
; 
; compilation unit finished
;   caught 1 ERROR condition
;   caught 1 WARNING condition
NIL
end transcript}

OK, the warnings are expected by design (SBCL is a bit... chatty) but
shouldn't the value be T regardless? Is this a bug in SBCL? I'm
running SBCL 1.0.6.

<snip>
> At least it gives you a fallback implementation for those
> implementations that don't have something better to offer.

Well... ;)
From: Juho Snellman
Subject: Re: Any programmable way to ask whether a symbol has been proclaimed special?
Date: 
Message-ID: <87k5hzyrft.fsf@vasara.proghammer.com>
Chris Barts <··············@gmail.com> writes:
> > (defun pervasively-special-p (var)
> >   (values
> >     (ignore-errors ;in case binding a constant doesn't work
> >       (eval `(let ((,var nil))
> >                (declare (special ,var))
> >                (let ((,var t))
> >                  (symbol-value ',var)))))))
[...]
> Except this fails on SBCL:
> 
> {begin transcript:
> CL-USER> (pervasively-special-p '*print-base*)
[...]
> OK, the warnings are expected by design (SBCL is a bit... chatty) but
> shouldn't the value be T regardless? Is this a bug in SBCL? I'm
> running SBCL 1.0.6.

No, it's not an SBCL bug. The code is invoking at least two bits of
undefined behaviour:

  * Declaring a symbol in CL special (11.1.2.1.2).
  * Binding the value of *print-base* to NIL and T, when it's defined
    by the spec to be a radix (1.4.4.22).

-- 
Juho Snellman
From: Kent M Pitman
Subject: Re: Any programmable way to ask whether a symbol has been proclaimed special?
Date: 
Message-ID: <u7idylvpv.fsf@nhplace.com>
Juho Snellman <······@iki.fi> writes:

> Chris Barts <··············@gmail.com> writes:
> > > (defun pervasively-special-p (var)
> > >   (values
> > >     (ignore-errors ;in case binding a constant doesn't work
> > >       (eval `(let ((,var nil))
> > >                (declare (special ,var))
> > >                (let ((,var t))
> > >                  (symbol-value ',var)))))))
> [...]
> > Except this fails on SBCL:
> > 
> > {begin transcript:
> > CL-USER> (pervasively-special-p '*print-base*)
> [...]
> > OK, the warnings are expected by design (SBCL is a bit... chatty) but
> > shouldn't the value be T regardless? Is this a bug in SBCL? I'm
> > running SBCL 1.0.6.
> 
> No, it's not an SBCL bug. The code is invoking at least two bits of
> undefined behaviour:
> 
>   * Declaring a symbol in CL special (11.1.2.1.2).

Yep, that's what it says.  Still, not that it matters because it's just
my personal point of view, I always thought of that as forbidding you 
from declaring system special that wasn't already special, that is, from
changing the behavior of a system-supplied symbol.  

>   * Binding the value of *print-base* to NIL and T, when it's defined
>     by the spec to be a radix (1.4.4.22).

You're just no fun. :)

Ok, I'll give it another go.  This should avoid a bunch of those details
everyone's nagging about.

(defun pervasively-special-p (var)
  (check-type var symbol "a variable name")
  (if (eq (symbol-package var) (load-time-value (find-package "CL")))
      (and (boundp var)
           (let* ((name (symbol-name var))
                  (n-chars (length name)))
             (and (> n-chars 0)
                  (eql (char name 0) #\*)
                  (eql (char name (- n-chars 1)) #\*)
                  :so-it-would-seem)))
     (values
       (handler-bind ((warning #'(lambda (warning)
                                   (when (find-restart 'muffle-warning warning)
                                     (muffle-warning warning)))))
         (ignore-errors ;in case binding a constant doesn't work
           (eval `(let ((,var nil))
                    (declare (special ,var))
                    (let ((,var t))
                      (symbol-value ',var)))))))))
From: ·······@ravenpack.com
Subject: Re: Any programmable way to ask whether a symbol has been proclaimed 	special?
Date: 
Message-ID: <6ec9a1bb-babf-4758-b054-b8bc1b34e301@e53g2000hsa.googlegroups.com>
Something simpler ought to be possible.  How about this?

(defun special-p (symbol)
  (if (constantp symbol)
      t ;; or change to nil if you think constants are not special...
    (let ((value (if (boundp symbol) (symbol-value symbol) '#:unique))
          (test `(lambda (,symbol)
                   (ignore-errors
                    (eq (symbol-value ',symbol) ,symbol)))))
      (values (funcall (coerce test 'function) value)))))


Seems to work (with no warnings) on ACL8.1 and SBCL.

-Jason
From: Rob Warnock
Subject: Re: Any programmable way to ask whether a symbol has been proclaimed special?
Date: 
Message-ID: <isKdndAS_6RnZ7rVnZ2dnUVZ_sHinZ2d@speakeasy.net>
Robert Maas <···················@SpamGourmet.Com> wrote:
+---------------
| Then suddenly I remembered DESCRIBE, which printed out among other things:
|   It is a special variable; no current value.
| OK, so I should have thought of that first. But there's no SPECIALP
| predicate or anything else I can find. How does DESCRIBE know that
| the symbol is special? How does the JIT compiler built into the
| REP loop know that it's special when it's deciding whether to do
| lexical or special bindings?
...
| This is in CMUCL, if it makes any difference. I'm hoping for some
| ANSI-CL function (predicate) rather than a CMUCL-specific function
| (predicate), but I'm curious in any case.
+---------------

I could give you a CMUCL-specific answer, involving macroexpanding
(DEFVAR *FOO*) [*without* setting a value] and then poking around
in the CMUCL sources and eventually finding that you might want to
use the dreaded infamous CMUCL "INFO" database that DESCRIBE uses
internally [see the source at "~cmucl-19c/src/code/describe.lisp"]:

    cmu> (info variable kind '*foo*)

    :GLOBAL
    NIL

    cmu> (defvar *foo*)

    *FOO*
    cmu> (info variable kind '*foo*)

    :SPECIAL
    T
    cmu> 

[Other possible answers for INFO VARIABLE KIND are :CONSTANT
(for DEFCONSTANT), :MACRO (for symbol macros), and :ALIEN (for
the CMUCL's "alien" FFI data), so you'd want to be prepared
for all of those, too. Similar things are available for INFO
FUNCTION KIND, but I don't think you really want to go there.]

But that's really a red herring, sorry to bring it up...  ;-}  ;-}

If you're trying to be portable, probably the best thing you can do
is send the output of DESCRIBE to a string stream and then use a
simple per-implementation pattern match to pull the info you need
out of it. That's likely to be more stable than any weird internal
interfaces [such as CMUCL's INFO], and *much* easier to add support
for new implementations:

    (defun globally-special-p (symbol)
      (let ((description (with-output-to-string (s) (describe symbol s))))
	#+cmu (search "It is a special variable" description)
	#+clisp (search "variable declared SPECIAL" description)
	;; Add more implementations here...
	#-(or cmu clisp)
	  (error "Not supported in ~A" (lisp-implementation-type))))

This group could probably flesh that out for a dozen more
implementations in only a handful of followup posts...  ;-}  ;-}


-Rob

-----
Rob Warnock			<····@rpw3.org>
627 26th Avenue			<URL:http://rpw3.org/>
San Mateo, CA 94403		(650)572-2607
From: Duane Rettig
Subject: Re: Any programmable way to ask whether a symbol has been proclaimed special?
Date: 
Message-ID: <o0od7bmu0p.fsf@gemini.franz.com>
···················@SpamGourmet.Com (Robert Maas,
http://tinyurl.com/uh3t) writes:

> Today I got in a situation where I thought I had declared a
> particular symbol to be special, by means of DEFVAR most likely,
> but was getting strange behaviour related to it. I wanted to
> diagnose the problem by first learning whether the symbol had been
> proclaimed special or not. I first looked on the property list of
> that symbol, but there was nothing there at all, no SPECIAL flag or
> anything like that. I then spent a half hour searching through
> CLtL1 without finding any predicate that tells whether a symbol is
> special (already) or not. I checked the HyperSpec and couldn't find
> any such predicate there either. Then suddenly I remembered
> DESCRIBE, which printed out among other things:
>   It is a special variable; no current value.
> OK, so I should have thought of that first. But there's no SPECIALP
> predicate or anything else I can find. How does DESCRIBE know that
> the symbol is special? How does the JIT compiler built into the
> REP loop know that it's special when it's deciding whether to do
> lexical or special bindings? If I ever want to automate the
> checking of several symbols to see if I forgot to proclaim any of
> them special, how can I do that, except by binding standard output
> to a string-output-string and calling DESCRIBE in that context and
> then parsing the resultant string of output from DESCRIBE??
>
> This is in CMUCL, if it makes any difference. I'm hoping for some
> ANSI-CL function (predicate) rather than a CMUCL-specific function
> (predicate), but I'm curious in any case.

I believe that Ray Toy has worked on putting in the CLtL2-style
Environments Access module:

http://www.lispwire.com/entry-proganal-envaccess-des

into CMUCL.  You might want to ask him about it.  Anyway, it would be
true that for any lisp that implements this module in the most
primitive level (see the powerpoint presentation in the project above)
the portable solution would be something like:

(defun specialp (name &optional env)
  (eq :special (sys:variable-information name env)))

This of course works in Allegro CL, but it may also work in CMUCL, if
the correct module is loaded.  Check with Ray Toy to be sure.

-- 
Duane Rettig    ·····@franz.com    Franz Inc.  http://www.franz.com/
555 12th St., Suite 1450               http://www.555citycenter.com/
Oakland, Ca. 94607        Phone: (510) 452-2000; Fax: (510) 452-0182