Lisp HUG Maillist Archive

unexpectedly "assumed special" warnings

Hi all,
Can anyone tell me why I get this warning?  (I don't get similar
warnings under SBCL or CCL.)

;;;*** Warning in NEGATIVE: #:*NEGATIVE* assumed special

The code follows. I'd have thought that the macroexpansion for 3)
would be just like the manually coded 2), but I get the warning in 3),
but not in 2).  Does this have something to do with the fact that the
symbol isn't interned anywhere?  In case 3) I can add a (declare
(special …)) to the function definition that gets rid of the warning,
but since progn's contents are top level forms, I'd have through that
the preceding defparameter should have already made the special
declaration pervasive.  Am I missing something?

;; lookup and maybe store a value in a hash-table (interning)

(defun get-or-set-interned-value (key hash-table value-function)
  (multiple-value-bind (value presentp)
      (gethash key hash-table)
    (if presentp value
      (setf (gethash key hash-table)
            (funcall value-function)))))


;; 1) here's a interner for squares (with no progn)

(defparameter *square* (make-hash-table))

(defun square (x)
  (get-or-set-interned-value
   x *square* #'(lambda () (* x x))))

;; 2) and an interner for cubes (in a progn)

(progn
(defparameter *cube* (make-hash-table))

(defun cube (x)
  (get-or-set-interned-value
   x *cube* #'(lambda () (* x x x))))
) ; progn

;; 3) here's a macro for defining interners, but I get an "... assumed
special" warning

(defmacro definterner (name (key) &body body)
  (let ((hash-table (make-symbol (concatenate 'string "*" (string name) "*"))))
  `(progn
     (defparameter ,hash-table (make-hash-table))
     (defun ,name (,key)
       (get-or-set-interned-value
        ,key ,hash-table #'(lambda () ,@body))))))

(definterner negative (x)
  (- x))

Thanks in advance.  I'll use the special declaration for now, but I'd
like to know why it's necessary.

-- 
Joshua Taylor, http://www.cs.rpi.edu/~tayloj/


Re: unexpectedly "assumed special" warnings

Joshua TAYLOR <tayloj@cs.rpi.edu> writes:

> Hi all,
> Can anyone tell me why I get this warning?  (I don't get similar
> warnings under SBCL or CCL.)
>
> ;;;*** Warning in NEGATIVE: #:*NEGATIVE* assumed special
>
> The code follows. I'd have thought that the macroexpansion for 3)
> would be just like the manually coded 2), but I get the warning in 3),
> but not in 2).  Does this have something to do with the fact that the
> symbol isn't interned anywhere?  In case 3) I can add a (declare
> (special …)) to the function definition that gets rid of the warning,
> but since progn's contents are top level forms, I'd have through that
> the preceding defparameter should have already made the special
> declaration pervasive.  Am I missing something?
>
> ;; lookup and maybe store a value in a hash-table (interning)
>
> (defun get-or-set-interned-value (key hash-table value-function)
>   (multiple-value-bind (value presentp)
>       (gethash key hash-table)
>     (if presentp value
>       (setf (gethash key hash-table)
>             (funcall value-function)))))
>
>
> ;; 1) here's a interner for squares (with no progn)
>
> (defparameter *square* (make-hash-table))
>
> (defun square (x)
>   (get-or-set-interned-value
>    x *square* #'(lambda () (* x x))))
>
> ;; 2) and an interner for cubes (in a progn)
>
> (progn
> (defparameter *cube* (make-hash-table))
>
> (defun cube (x)
>   (get-or-set-interned-value
>    x *cube* #'(lambda () (* x x x))))
> ) ; progn
>
> ;; 3) here's a macro for defining interners, but I get an "... assumed
> special" warning
>
> (defmacro definterner (name (key) &body body)
>   (let ((hash-table (make-symbol (concatenate 'string "*" (string name) "*"))))
>   `(progn
>      (defparameter ,hash-table (make-hash-table))
>      (defun ,name (,key)
>        (get-or-set-interned-value
>         ,key ,hash-table #'(lambda () ,@body))))))
>
> (definterner negative (x)
>   (- x))
>
> Thanks in advance.  I'll use the special declaration for now, but I'd
> like to know why it's necessary.
>
> -- 
> Joshua Taylor, http://www.cs.rpi.edu/~tayloj/


After the macro expansion ...

 > (macroexpand-1 '(definterner negative (x) (- x)))
(PROGN
  (DEFPARAMETER #:*NEGATIVE* (MAKE-HASH-TABLE))
  (DEFUN NEGATIVE (X)
  (GET-OR-SET-INTERNED-VALUE X #:*NEGATIVE* (FUNCTION (LAMBDA NIL (- X))))))
T

.... the two occurrences of #:*negative* are not the same symbol, so the
second one is assumed special (because it was not declared special).
The reader macro #: "introduces an uninterned symbol ... Every time this
syntax is encountered, a distinct uninterned symbol is created."
(http://www.lispworks.com/documentation/HyperSpec/Body/02_dhe.htm)

Your problem is with the use of MAKE-SYMBOL, which "creates and returns
a fresh, uninterned symbol whose name is the given name", i.e. why
*negative* is preceded by #: in the macro expansion.
(http://www.lispworks.com/documentation/HyperSpec/Body/f_mk_sym.htm)

What you want to use is the INTERN function:
(http://www.lispworks.com/documentation/HyperSpec/Body/f_intern.htm)

(defmacro definterner (name (key) &body body)
  (let ((hash-table (intern (concatenate 'string "*" (string name) "*"))))
    `(progn
       (defparameter ,hash-table (make-hash-table))
       (defun ,name (,key)
         (get-or-set-interned-value
          ,key ,hash-table #'(lambda () ,@body))))))

HTH.
Nico


Re: unexpectedly "assumed special" warnings

Joshua TAYLOR <tayloj@cs.rpi.edu> writes:

> On Tue, Mar 30, 2010 at 4:23 PM, Nico de Jager <ndj@bitart.cc> wrote:
>> After the macro expansion ...
>>
>>  > (macroexpand-1 '(definterner negative (x) (- x)))
>> (PROGN
>>  (DEFPARAMETER #:*NEGATIVE* (MAKE-HASH-TABLE))
>>  (DEFUN NEGATIVE (X)
>>  (GET-OR-SET-INTERNED-VALUE X #:*NEGATIVE* (FUNCTION (LAMBDA NIL (- X))))))
>> T
>>
>> ... the two occurrences of #:*negative* are not the same symbol, so the
>> second one is assumed special (because it was not declared special).
>> The reader macro #: "introduces an uninterned symbol ... Every time this
>> syntax is encountered, a distinct uninterned symbol is created."
>> (http://www.lispworks.com/documentation/HyperSpec/Body/02_dhe.htm)
>
> They are the same symbol. The macroexpansion has the same
> (uninterned) symbol in two places.  Printing the macroexpansion with
> *print-circle* bound to T shows this:
>
> CL-USER 5 > (let ((*print-circle* t))
>               (pprint (macroexpand-1 '(definterner negative (x) (- x)))))
>
> (PROGN
>   (DEFPARAMETER #1=#:*NEGATIVE* (MAKE-HASH-TABLE))
>   (DEFUN NEGATIVE (X) (GET-OR-SET-INTERNED-VALUE X #1# #'(LAMBDA () (- X)))))

My mental model of this, is that they are the same uninterned symbol
during macroexpansion time, but not afterwards: 

CL-USER 61 > (with-output-to-string (s)
               (prin1 (macroexpand-1 '(definterner negative (x) (- x))) s))
"(PROGN (DEFPARAMETER #:*NEGATIVE* (MAKE-HASH-TABLE)) (DEFUN NEGATIVE (X) (GET-OR-SET-INTERNED-VALUE X #:*NEGATIVE* (FUNCTION (LAMBDA NIL (- X))))))"

CL-USER 62 > (defparameter *full* (read-from-string *))
*FULL*

CL-USER 63 > *full*
(PROGN (DEFPARAMETER #:*NEGATIVE* (MAKE-HASH-TABLE)) (DEFUN NEGATIVE (X) (GET-OR-SET-INTERNED-VALUE X #:*NEGATIVE* (FUNCTION (LAMBDA NIL (- X))))))

CL-USER 64 > (defparameter *neg1* (cadadr *full*))
*NEG1*

CL-USER 65 > (defparameter *neg2* (third (cadddr (third  *full*))))
*NEG2*

CL-USER 66 > *neg1*
#:*NEGATIVE*

CL-USER 67 > *neg2*
#:*NEGATIVE*

CL-USER 68 > (eq *neg1* *neg2*)
NIL


>> Your problem is with the use of MAKE-SYMBOL, which "creates and returns
>> a fresh, uninterned symbol whose name is the given name", i.e. why
>> *negative* is preceded by #: in the macro expansion.
>> (http://www.lispworks.com/documentation/HyperSpec/Body/f_mk_sym.htm)
>>
>> What you want to use is the INTERN function:
>> (http://www.lispworks.com/documentation/HyperSpec/Body/f_intern.htm)
>
> My intention is for the symbol not to be interned in any package;

Off course, you did not state this in your original post.


> I
> don't intend to provide (easy) access to the hash-table except through
> the provided interface.  (In my example, making the name begin with
> #\* and #\* might have made this unclear.  I'd only done that to
> ensure that LW wasn't applying some heuristic that warned about
> unconventionally-name specials.)


Re: unexpectedly "assumed special" warnings

On 30 Mar 2010, at 19:17, Joshua TAYLOR wrote:

> Hi all,
> Can anyone tell me why I get this warning?  (I don't get similar
> warnings under SBCL or CCL.)

I can't, and I don't think you should. I think I'd probably do it  
differently (for instance have a single secret global hashtable in  
which you store the other hashtables rather than lots of global  
gensymmed specials), but I think what you're doing is OK.

In particular the expansion of the macro looks like

(progn
   (defparameter X ...)
   (defun ... (...)
     ... use variable X ...))

where X is a gensym. If this is at top-level, then the DEFPARAMETER  
and DEFUN are also at toplevel, and the compiler is required to notice  
that the variable is special (see http://www.lispworks.com/documentation/HyperSpec/Body/m_defpar.htm) 
..

The only thing I can see which would cause problems is if the thing is  
*not* being evaluated at top-level, and that might be the case if you  
are evaluating it in the editor or something like that.  Do you get  
these warnings if you put everything in a file and compile it in a  
cold lisp?

--tim


Re: unexpectedly "assumed special" warnings

Unable to parse email body. Email id is 10137

Re: unexpectedly "assumed special" warnings

Joshua TAYLOR <tayloj@cs.rpi.edu> writes:

> If the macroexpansion created a string which was then re-read by the
> reader, your mental model would be correct, but the actual Lisp object
> that the macro produces is given to the system.  That's why we can do
> things like:
> ....
> Hope this makes things a bit clearer.

Yes, it does. I should have realized from my general understanding of
macros and gensym that my explanation is wrong (stupid, in fact). Thank
you for taking the time to show it explicitly.


Updated at: 2020-12-10 08:39 UTC