Simpify (X - (X & mask)) to (X & ~mask)
[sbcl.git] / src / code / symbol.lisp
blob3a4ec171a1355f2d985444bb1ce05d63ba8fb8ad
1 ;;;; code to manipulate symbols (but not packages, which are handled
2 ;;;; elsewhere)
3 ;;;;
4 ;;;; Many of these definitions are trivial interpreter entries to
5 ;;;; functions open-coded by the compiler.
7 ;;;; This software is part of the SBCL system. See the README file for
8 ;;;; more information.
9 ;;;;
10 ;;;; This software is derived from the CMU CL system, which was
11 ;;;; written at Carnegie Mellon University and released into the
12 ;;;; public domain. The software is in the public domain and is
13 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
14 ;;;; files for more information.
16 (in-package "SB!IMPL")
18 (declaim (maybe-inline get3 %put getf remprop %putf get-properties keywordp))
20 (defun symbol-value (symbol)
21 "Return SYMBOL's current bound value."
22 (declare (optimize (safety 1)))
23 (symbol-value symbol))
25 (defun boundp (symbol)
26 "Return non-NIL if SYMBOL is bound to a value."
27 (boundp symbol))
29 (defun set (symbol new-value)
30 "Set SYMBOL's value cell to NEW-VALUE."
31 (declare (type symbol symbol))
32 (about-to-modify-symbol-value symbol 'set new-value)
33 (%set-symbol-value symbol new-value))
35 (defun %set-symbol-value (symbol new-value)
36 (%set-symbol-value symbol new-value))
38 (defun symbol-global-value (symbol)
39 "Return the SYMBOL's current global value. Identical to SYMBOL-VALUE,
40 in single-threaded builds: in multithreaded builds bound values are
41 distinct from the global value. Can also be SETF."
42 (declare (optimize (safety 1)))
43 (symbol-global-value symbol))
45 (defun set-symbol-global-value (symbol new-value)
46 (about-to-modify-symbol-value symbol 'set new-value)
47 (%set-symbol-global-value symbol new-value))
49 (declaim (inline %makunbound))
50 (defun %makunbound (symbol)
51 (%set-symbol-value symbol (make-unbound-marker)))
53 (defun makunbound (symbol)
54 "Make SYMBOL unbound, removing any value it may currently have."
55 (with-single-package-locked-error (:symbol symbol "unbinding the symbol ~A")
56 ;; :EVENTUALLY is allowed for :always-bound here, as it has no bearing
57 (when (eq (info :variable :always-bound symbol) :always-bound)
58 (error "Can't make ~A variable unbound: ~S" 'always-bound symbol))
59 (about-to-modify-symbol-value symbol 'makunbound)
60 (when (eq (info :variable :kind symbol) :constant)
61 (clear-info :variable :kind symbol))
62 (%makunbound symbol)
63 symbol))
65 ;; Compute a symbol's hash. Also used by FIND-SYMBOL which requires that a hash
66 ;; be a pure function of the name and not a semi-opaque property of the symbol.
67 ;; The hash of all symbols named "NIL" must be the same, so not to pessimize
68 ;; FIND-SYMBOL by special-casing the finding of CL:NIL with an extra "or"
69 ;; in the hash-equality test. i.e. We can't recognize that CL:NIL was the
70 ;; object sought (having an exceptional hash) until it has been found.
71 (defun compute-symbol-hash (string length)
72 (declare (simple-string string) (index length))
73 (if (and (= length 3)
74 (locally
75 ;; SXHASH-SUBSTRING is unsafe, so this is too. but do we know that
76 ;; length is ok, or is it an accident that it can scan too far?
77 (declare (optimize (safety 0)))
78 (string-dispatch (simple-base-string (simple-array character (*)))
79 string
80 (and (char= (schar string 0) #\N)
81 (char= (schar string 1) #\I)
82 (char= (schar string 2) #\L)))))
83 (return-from compute-symbol-hash (sxhash nil)))
84 ;; And make a symbol's hash not the same as (sxhash name) in general.
85 (let ((sxhash (logand (lognot (%sxhash-simple-substring string length))
86 sb!xc:most-positive-fixnum)))
87 (if (zerop sxhash) #x55AA sxhash))) ; arbitrary substitute for 0
89 ;; Return SYMBOL's hash, a strictly positive fixnum, computing it if not stored.
90 ;; The inlined code for (SXHASH symbol) only calls ENSURE-SYMBOL-HASH if
91 ;; needed, however this is ok to call even if the hash is already nonzero.
92 (defun ensure-symbol-hash (symbol)
93 (let ((hash (symbol-hash symbol)))
94 (if (zerop hash)
95 (let ((name (symbol-name symbol)))
96 (%set-symbol-hash symbol (compute-symbol-hash name (length name))))
97 hash)))
99 ;;; Interpreter stub: Return whatever is in the SYMBOL-HASH slot of SYMBOL.
100 (defun symbol-hash (symbol)
101 (symbol-hash symbol))
103 (defun symbol-function (symbol)
104 "Return SYMBOL's current function definition. Settable with SETF."
105 (%coerce-name-to-fun symbol symbol-fdefn))
107 ;; I think there are two bugs here.
108 ;; Per CLHS "SETF may be used with symbol-function to replace a global
109 ;; function definition when the symbol's function definition
110 ;; does not represent a special operator."
111 ;; 1. This should fail:
112 ;; * (in-package CL) ; circumvent package lock
113 ;; * (setf (symbol-function 'if) #'cons) => #<FUNCTION CONS>
114 ;; 2. (SETF (SYMBOL-FUNCTION 'I-ONCE-WAS-A-MACRO) #'CONS)
115 ;; should _probably_ make I-ONCE-WAS-A-MACRO not a macro
116 (defun (setf symbol-function) (new-value symbol)
117 (declare (type symbol symbol) (type function new-value))
118 ;; (SYMBOL-FUNCTION symbol) == (FDEFINITION symbol) according to the writeup
119 ;; on SYMBOL-FUNCTION. It doesn't say that SETF behaves the same, but let's
120 ;; assume it does, and that we can't assign our macro/special guard funs.
121 (err-if-unacceptable-function new-value '(setf symbol-function))
122 (with-single-package-locked-error
123 (:symbol symbol "setting the symbol-function of ~A")
124 ;; This code is a little "surprising" in that it is not just a limited
125 ;; case of (SETF FDEFINITION), but instead a different thing.
126 ;; I really think the code paths should be reconciled.
127 ;; e.g. what's up with *USER-HASH-TABLE-TESTS* being checked
128 ;; in %SET-FDEFINITION but not here?
129 (maybe-clobber-ftype symbol new-value)
130 (let ((fdefn (find-or-create-fdefn symbol)))
131 (setf (fdefn-fun fdefn) new-value))))
133 ;;; Accessors for the dual-purpose info/plist slot
135 ;; A symbol's INFO slot is always in one of three states:
136 ;; 1. NIL ; the initial state
137 ;; 2. #(data ....) ; globaldb used the slot
138 ;; 3. (PLIST . NIL) or (PLIST . #(data ...)) ; plist was touched,
139 ;; and also possibly globaldb used the slot
141 ;; State 1 transitions to state 2 by assigning globaldb data,
142 ;; or to state 3 via ({SETF|CAS} SYMBOL-PLIST).
143 ;; (SETF INFO) by itself will never cause 1 -> 3 transition.
144 ;; State 2 transitions to state 3 via ({SETF|CAS} SYMBOL-PLIST).
145 ;; There are *no* other permissible state transitions.
147 (defun symbol-info (symbol)
148 (symbol-info symbol))
150 ;; An "interpreter stub" for an operation that is only implemented for
151 ;; the benefit of platforms without compare-and-swap-vops.
152 (defun (setf symbol-info) (new-info symbol)
153 (setf (symbol-info symbol) new-info))
155 ;; Atomically update SYMBOL's info/plist slot to contain a new info vector.
156 ;; The vector is computed by calling UPDATE-FN on the old vector,
157 ;; repeatedly as necessary, until no conflict happens with other updaters.
158 ;; The function may choose to abort the update by returning NIL.
159 (defun update-symbol-info (symbol update-fn)
160 (declare (symbol symbol)
161 (type (function (t) t) update-fn))
162 (prog ((info-holder (symbol-info symbol))
163 (current-vect))
164 outer-restart
165 ;; Do not use SYMBOL-INFO-VECTOR - this must not perform a slot read again.
166 (setq current-vect (if (listp info-holder) (cdr info-holder) info-holder))
167 inner-restart
168 (let ((new-vect (funcall update-fn (or current-vect +nil-packed-infos+))))
169 (unless (simple-vector-p new-vect)
170 (aver (null new-vect))
171 (return)) ; nothing to do
172 (if (consp info-holder) ; State 3: exchange the CDR
173 (let ((old (%compare-and-swap-cdr info-holder current-vect new-vect)))
174 (when (eq old current-vect) (return t)) ; win
175 (setq current-vect old) ; Don't touch holder- it's still a cons
176 (go inner-restart)))
177 ;; State 1 or 2: info-holder is NIL or a vector.
178 ;; Exchange the contents of the info slot. Type-inference derives
179 ;; SIMPLE-VECTOR-P on the args to CAS, so no extra checking.
180 (let ((old (%compare-and-swap-symbol-info symbol info-holder new-vect)))
181 (when (eq old info-holder) (return t)) ; win
182 ;; Check whether we're in state 2 or 3 now.
183 ;; Impossible to be in state 1: nobody ever puts NIL in the slot.
184 ;; Up above, we bailed out if the update-fn returned NIL.
185 (setq info-holder old)
186 (go outer-restart)))))
188 (eval-when (:compile-toplevel)
189 ;; If we're in state 1 or state 3, we can take (CAR (SYMBOL-INFO S))
190 ;; to get the property list. If we're in state 2, this same access
191 ;; gets the fixnum which is the VECTOR-LENGTH of the info vector.
192 ;; So all we have to do is turn any fixnum to NIL, and we have a plist.
193 ;; Ensure that this pun stays working.
194 (assert (= (- (* sb!vm:n-word-bytes sb!vm:cons-car-slot)
195 sb!vm:list-pointer-lowtag)
196 (- (* sb!vm:n-word-bytes sb!vm:vector-length-slot)
197 sb!vm:other-pointer-lowtag))))
199 (defun symbol-plist (symbol)
200 "Return SYMBOL's property list."
201 #!+symbol-info-vops
202 (symbol-plist symbol) ; VOP translates it
203 #!-symbol-info-vops
204 (let ((list (car (truly-the list (symbol-info symbol))))) ; a white lie
205 ;; Just ensure the result is not a fixnum, and we're done.
206 (if (fixnump list) nil list)))
208 (declaim (ftype (sfunction (symbol t) cons) %ensure-plist-holder)
209 (inline %ensure-plist-holder))
211 ;; When a plist update (setf or cas) is first performed on a symbol,
212 ;; a one-time allocation of an extra cons is done which creates two
213 ;; "slots" from one: a slot for the info-vector and a slot for the plist.
214 ;; This avoids complications in the implementation of the user-facing
215 ;; (CAS SYMBOL-PLIST) function, which should not have to be aware of
216 ;; competition from globaldb mutators even if no other threads attempt
217 ;; to manipulate the plist per se.
219 ;; Given a SYMBOL and its current INFO of type (OR LIST SIMPLE-VECTOR)
220 ;; ensure that SYMBOL's current info is a cons, and return that.
221 ;; If racing with multiple threads, at most one thread will install the cons.
222 (defun %ensure-plist-holder (symbol info)
223 ;; Invoked only when SYMBOL is known to be a symbol.
224 (declare (optimize (safety 0)))
225 (if (consp info) ; it's fine to call this with a cell already installed
226 info ; all done
227 (let (newcell)
228 ;; The pointer from the new cons to the old info must be persisted
229 ;; to memory before the symbol's info slot points to the cons.
230 ;; [x86oid doesn't need the barrier, others might]
231 (sb!thread:barrier (:write)
232 (setq newcell (cons nil info)))
233 (loop (let ((old (%compare-and-swap-symbol-info symbol info newcell)))
234 (cond ((eq old info) (return newcell)) ; win
235 ((consp old) (return old))) ; somebody else made a cons!
236 (setq info old)
237 (sb!thread:barrier (:write) ; Retry using same newcell
238 (rplacd newcell info)))))))
240 (declaim (inline %compare-and-swap-symbol-plist
241 %set-symbol-plist))
243 (defun %compare-and-swap-symbol-plist (symbol old new)
244 ;; This is the entry point into which (CAS SYMBOL-PLIST) is transformed.
245 ;; If SYMBOL's info cell is a cons, we can do (CAS CAR). Otherwise punt.
246 (declare (symbol symbol) (list old new))
247 (let ((cell (symbol-info symbol)))
248 (if (consp cell)
249 (%compare-and-swap-car cell old new)
250 (%%compare-and-swap-symbol-plist symbol old new))))
252 (defun %%compare-and-swap-symbol-plist (symbol old new)
253 ;; This is just the second half of a partially-inline function, to avoid
254 ;; code bloat in the exceptional case. Type assertions should have been
255 ;; done - or not, per policy - by the caller of %COMPARE-AND-SWAP-SYMBOL-PLIST
256 ;; so now use TRULY-THE to avoid further type checking.
257 (%compare-and-swap-car (%ensure-plist-holder (truly-the symbol symbol)
258 (symbol-info symbol))
259 old new))
261 (defun %set-symbol-plist (symbol new-value)
262 ;; This is the entry point into which (SETF SYMBOL-PLIST) is transformed.
263 ;; If SYMBOL's info cell is a cons, we can do (SETF CAR). Otherwise punt.
264 (declare (symbol symbol) (list new-value))
265 (let ((cell (symbol-info symbol)))
266 (if (consp cell)
267 (setf (car cell) new-value)
268 (%%set-symbol-plist symbol new-value))))
270 (defun %%set-symbol-plist (symbol new-value)
271 ;; Same considerations as for %%COMPARE-AND-SWAP-SYMBOL-PLIST,
272 ;; with a slight efficiency hack: if the symbol has no plist holder cell
273 ;; and the NEW-VALUE is NIL, try to avoid creating a holder cell.
274 ;; Yet we must write something, because omitting a memory operation
275 ;; could have a subtle effect in the presence of multi-threading.
276 (let ((info (symbol-info (truly-the symbol symbol))))
277 (when (and (not new-value) (atom info)) ; try to treat this as a no-op
278 (let ((old (%compare-and-swap-symbol-info symbol info info)))
279 (if (eq old info) ; good enough
280 (return-from %%set-symbol-plist new-value) ; = nil
281 (setq info old))))
282 (setf (car (%ensure-plist-holder symbol info)) new-value)))
284 ;;; End of Info/Plist slot manipulation
286 (defun symbol-name (symbol)
287 "Return SYMBOL's name as a string."
288 (symbol-name symbol))
290 (defun symbol-package (symbol)
291 "Return the package SYMBOL was interned in, or NIL if none."
292 (symbol-package symbol))
294 (defun %set-symbol-package (symbol package)
295 (declare (type symbol symbol))
296 (%set-symbol-package symbol package))
298 (defun make-symbol (string)
299 "Make and return a new symbol with the STRING as its print name."
300 (declare (type string string))
301 (%make-symbol 0 (if (simple-string-p string) string (subseq string 0))))
303 ;;; All symbols go into immobile space if #!+immobile-symbols is enabled,
304 ;;; but not if disabled. The win with immobile space that is that all symbols
305 ;;; can be considered static from an addressing viewpoint, but GC'able.
306 ;;; (After codegen learns how, provided that defrag becomes smart enough
307 ;;; to fixup machine code so that defrag remains meaningful)
309 ;;; However, with immobile space being limited in size, you might not want
310 ;;; symbols in there. In particular, if an application uses symbols as data
311 ;;; - perhaps symbolic algebra on a Raspberry Pi - then not only is a faster
312 ;;; purely Lisp allocator better, you probably want not to run out of space.
313 ;;; The plausible heuristic that interned symbols be immobile, and otherwise not,
314 ;;; is mostly ok, except for the unfortunate possibility of calling IMPORT
315 ;;; on a random gensym. And even if a symbol is in immobile space at compile-time,
316 ;;; it might not be at load-time, if you do nasty things like that, so really
317 ;;; we can't make any reasonable determination - it's sort of all or nothing.
319 ;;; We can perhaps hardcode addresses of keywords in any case if we think that
320 ;;; people aren't in the habit of importing gensyms into #<package KEYWORD>.
321 ;;; It's kinda useless to do that, though not technically forbidden.
322 ;;; (It can produce a not-necessarily-self-evaluating keyword)
324 #!+immobile-space
325 (defun %make-symbol (kind name)
326 (declare (ignorable kind) (type simple-string name))
327 (set-header-data name sb!vm:+vector-shareable+) ; Set "logically read-only" bit
328 (if #!-immobile-symbols
329 (or (eql kind 1) ; keyword
330 (and (eql kind 2) ; random interned symbol
331 (plusp (length name))
332 (char= (char name 0) #\*)
333 (char= (char name (1- (length name))) #\*)))
334 #!+immobile-symbols t ; always place them there
335 (truly-the (values symbol) (%primitive sb!vm::alloc-immobile-symbol name))
336 (sb!vm::%%make-symbol name)))
338 (defun get (symbol indicator &optional (default nil))
339 "Look on the property list of SYMBOL for the specified INDICATOR. If this
340 is found, return the associated value, else return DEFAULT."
341 (get3 symbol indicator default))
343 (defun get3 (symbol indicator default)
344 (let (cdr-pl)
345 (do ((pl (symbol-plist symbol) (cdr cdr-pl)))
346 ((atom pl) default)
347 (setq cdr-pl (cdr pl))
348 (cond ((atom cdr-pl)
349 (error "~S has an odd number of items in its property list."
350 symbol))
351 ((eq (car pl) indicator)
352 (return (car cdr-pl)))))))
354 (defun %put (symbol indicator value)
355 "The VALUE is added as a property of SYMBOL under the specified INDICATOR.
356 Returns VALUE."
357 (do ((pl (symbol-plist symbol) (cddr pl)))
358 ((endp pl)
359 (setf (symbol-plist symbol)
360 (list* indicator value (symbol-plist symbol)))
361 value)
362 (cond ((endp (cdr pl))
363 (error "~S has an odd number of items in its property list."
364 symbol))
365 ((eq (car pl) indicator)
366 (rplaca (cdr pl) value)
367 (return value)))))
369 (defun remprop (symbol indicator)
370 "Look on property list of SYMBOL for property with specified
371 INDICATOR. If found, splice this indicator and its value out of
372 the plist, and return the tail of the original list starting with
373 INDICATOR. If not found, return () with no side effects.
375 NOTE: The ANSI specification requires REMPROP to return true (not false)
376 or false (the symbol NIL). Portable code should not rely on any other value."
377 (do ((pl (symbol-plist symbol) (cddr pl))
378 (prev nil pl))
379 ((atom pl) nil)
380 (cond ((atom (cdr pl))
381 (error "~S has an odd number of items in its property list."
382 symbol))
383 ((eq (car pl) indicator)
384 (cond (prev (rplacd (cdr prev) (cddr pl)))
386 (setf (symbol-plist symbol) (cddr pl))))
387 (return pl)))))
389 (defun getf (place indicator &optional (default ()))
390 "Search the property list stored in PLACE for an indicator EQ to INDICATOR.
391 If one is found, return the corresponding value, else return DEFAULT."
392 (do ((plist place (cddr plist)))
393 ((null plist) default)
394 (cond ((atom (cdr plist))
395 (error 'simple-type-error
396 :format-control "malformed property list: ~S."
397 :format-arguments (list place)
398 :datum (cdr plist)
399 :expected-type 'cons))
400 ((eq (car plist) indicator)
401 (return (cadr plist))))))
403 (defun %putf (place property new-value)
404 (declare (type list place))
405 (do ((plist place (cddr plist)))
406 ((endp plist) (list* property new-value place))
407 (declare (type list plist))
408 (when (eq (car plist) property)
409 (setf (cadr plist) new-value)
410 (return place))))
412 (defun get-properties (place indicator-list)
413 "Like GETF, except that INDICATOR-LIST is a list of indicators which will
414 be looked for in the property list stored in PLACE. Three values are
415 returned, see manual for details."
416 (do ((plist place (cddr plist)))
417 ((null plist) (values nil nil nil))
418 (cond ((atom (cdr plist))
419 (error 'simple-type-error
420 :format-control "malformed property list: ~S."
421 :format-arguments (list place)
422 :datum (cdr plist)
423 :expected-type 'cons))
424 ((memq (car plist) indicator-list)
425 (return (values (car plist) (cadr plist) plist))))))
427 (defun copy-symbol (symbol &optional (copy-props nil) &aux new-symbol)
428 "Make and return a new uninterned symbol with the same print name
429 as SYMBOL. If COPY-PROPS is false, the new symbol is neither bound
430 nor fbound and has no properties, else it has a copy of SYMBOL's
431 function, value and property list."
432 (declare (type symbol symbol))
433 (setq new-symbol (make-symbol (symbol-name symbol)))
434 (when copy-props
435 (%set-symbol-value new-symbol
436 (%primitive sb!c:fast-symbol-value symbol))
437 (setf (symbol-plist new-symbol)
438 (copy-list (symbol-plist symbol)))
439 (when (fboundp symbol)
440 (setf (symbol-function new-symbol) (symbol-function symbol))))
441 new-symbol)
443 (defun keywordp (object)
444 "Return true if Object is a symbol in the \"KEYWORD\" package."
445 (and (symbolp object)
446 (eq (symbol-package object) *keyword-package*)))
448 ;;;; GENSYM and friends
450 (defvar *gentemp-counter* 0)
451 (declaim (type unsigned-byte *gentemp-counter*))
453 (flet ((%symbol-nameify (prefix counter)
454 (declare (string prefix))
455 (if (typep counter '(and fixnum unsigned-byte))
456 (let ((s ""))
457 (declare (simple-string s))
458 (labels ((recurse (depth n)
459 (multiple-value-bind (q r) (truncate n 10)
460 (if (plusp q)
461 (recurse (1+ depth) q)
462 (let ((et (if (or (base-string-p prefix)
463 #!+sb-unicode ; no #'base-char-p
464 (every #'base-char-p prefix))
465 'base-char 'character)))
466 (setq s (make-string (+ (length prefix) depth)
467 :element-type et))
468 (replace s prefix)))
469 (setf (char s (- (length s) depth))
470 (code-char (+ (char-code #\0) r)))
471 s)))
472 (recurse 1 counter)))
473 (with-simple-output-to-string (s)
474 (write-string prefix s)
475 (%output-integer-in-base counter 10 s)))))
477 (defvar *gensym-counter* 0
478 "counter for generating unique GENSYM symbols")
480 (defun gensym (&optional (thing "G"))
481 "Creates a new uninterned symbol whose name is a prefix string (defaults
482 to \"G\"), followed by a decimal number. Thing, when supplied, will
483 alter the prefix if it is a string, or be used for the decimal number
484 if it is a number, of this symbol. The default value of the number is
485 the current value of *gensym-counter* which is incremented each time
486 it is used."
487 (multiple-value-bind (prefix int)
488 (if (integerp thing)
489 (values "G" thing)
490 (values thing (let ((old *gensym-counter*))
491 (setq *gensym-counter* (1+ old))
492 old)))
493 (make-symbol (%symbol-nameify prefix int))))
495 (defun gentemp (&optional (prefix "T") (package (sane-package)))
496 "Creates a new symbol interned in package PACKAGE with the given PREFIX."
497 (loop (multiple-value-bind (sym accessibility)
498 (intern (%symbol-nameify prefix (incf *gentemp-counter*)) package)
499 (unless accessibility (return sym))))))
501 ;;; This function is to be called just before a change which would affect the
502 ;;; symbol value. We don't absolutely have to call this function before such
503 ;;; changes, since such changes to constants are given as undefined behavior,
504 ;;; it's nice to do so. To circumvent this you need code like this:
506 ;;; (defvar foo)
507 ;;; (defun set-foo (x) (setq foo x))
508 ;;; (defconstant foo 42)
509 ;;; (set-foo 13)
510 ;;; foo => 13, (constantp 'foo) => t
512 ;;; ...in which case you frankly deserve to lose.
513 (defun about-to-modify-symbol-value (symbol action &optional (new-value nil valuep) bind)
514 (declare (symbol symbol))
515 (declare (explicit-check))
516 (flet ((describe-action ()
517 (ecase action
518 (set "set SYMBOL-VALUE of ~S")
519 (progv "bind ~S")
520 (compare-and-swap "compare-and-swap SYMBOL-VALUE of ~S")
521 (defconstant "define ~S as a constant")
522 (makunbound "make ~S unbound"))))
523 (let ((kind (info :variable :kind symbol)))
524 (multiple-value-bind (what continue)
525 (cond ((eq kind :constant)
526 (cond ((eq symbol t)
527 (values "Veritas aeterna. (can't ~@?)" nil))
528 ((eq symbol nil)
529 (values "Nihil ex nihil. (can't ~@?)" nil))
530 ((keywordp symbol)
531 (values "Can't ~@?." nil))
533 (values "Constant modification: attempt to ~@?." t))))
534 ((and bind (eq kind :global))
535 (values "Can't ~@? (global variable)." nil))
536 ((and (eq action 'set)
537 (eq kind :unknown))
538 (with-single-package-locked-error
539 (:symbol symbol "setting the value of ~S"))
540 nil))
541 (when what
542 (if continue
543 (cerror "Modify the constant." what (describe-action) symbol)
544 (error what (describe-action) symbol)))
545 (when valuep
546 (multiple-value-bind (type declaredp) (info :variable :type symbol)
547 ;; If globaldb returned the default of *UNIVERSAL-TYPE*,
548 ;; don't bother with a type test.
549 (when (and declaredp (not (%%typep new-value type nil)))
550 (let ((spec (type-specifier type)))
551 (error 'simple-type-error
552 :format-control "~@<Cannot ~@? to ~S, not of type ~S.~:@>"
553 :format-arguments (list (describe-action) symbol new-value spec)
554 :datum new-value
555 :expected-type spec)))))))
556 nil))