run-program: support I/O redirection to binary streams on win32.
[sbcl.git] / src / code / symbol.lisp
blob22dd1e44041106e2921384e501f11744a4a4b0d1
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 ;;; Used by [GLOBAL-]SYMBOL-VALUE compiler-macros:
21 ;;;
22 ;;; When SYMBOL is constant, check whether it names a deprecated
23 ;;; variable, potentially signaling a {EARLY,LATE}-DEPRECATION-WARNING
24 ;;; in the process. Furthermore, if the deprecation state is :FINAL,
25 ;;; replace FORM by SYMBOL, causing the symbol-macro on SYMBOL to
26 ;;; expand into a call to DEPRECATION-ERROR.
27 ;;;
28 ;;; See SB-IMPL:SETUP-VARIABLE-IN-FINAL-DEPRECATION.
29 #-sb-xc-host
30 (eval-when (:compile-toplevel :load-toplevel :execute)
31 (defun maybe-handle-deprecated-global-variable (symbol env)
32 (when (sb!xc:constantp symbol env)
33 (let ((name (constant-form-value symbol env)))
34 (when (symbolp name)
35 (case (deprecated-thing-p 'variable name)
36 ((:early :late)
37 (check-deprecated-thing 'variable name)
38 nil)
39 ;; In this case, there is a symbol-macro for NAME that
40 ;; will signal the FINAL-DEPRECATION-WARNING when
41 ;; ir1converted and the DEPRECATION-ERROR at runtime.
42 (:final
43 name)))))))
45 (defun symbol-value (symbol)
46 #!+sb-doc
47 "Return SYMBOL's current bound value."
48 (declare (optimize (safety 1)))
49 (symbol-value symbol))
51 #-sb-xc-host
52 (define-compiler-macro symbol-value (&whole form symbol &environment env)
53 (or (maybe-handle-deprecated-global-variable symbol env) form))
55 (defun boundp (symbol)
56 #!+sb-doc
57 "Return non-NIL if SYMBOL is bound to a value."
58 (boundp symbol))
60 (defun set (symbol new-value)
61 #!+sb-doc
62 "Set SYMBOL's value cell to NEW-VALUE."
63 (declare (type symbol symbol))
64 (about-to-modify-symbol-value symbol 'set new-value)
65 (%set-symbol-value symbol new-value))
67 (defun %set-symbol-value (symbol new-value)
68 (%set-symbol-value symbol new-value))
70 (defun symbol-global-value (symbol)
71 #!+sb-doc
72 "Return the SYMBOL's current global value. Identical to SYMBOL-VALUE,
73 in single-threaded builds: in multithreaded builds bound values are
74 distinct from the global value. Can also be SETF."
75 (declare (optimize (safety 1)))
76 (symbol-global-value symbol))
78 #-sb-xc-host
79 (define-compiler-macro symbol-global-value (&whole form symbol
80 &environment env)
81 (or (maybe-handle-deprecated-global-variable symbol env) form))
83 (defun set-symbol-global-value (symbol new-value)
84 (about-to-modify-symbol-value symbol 'set new-value)
85 (%set-symbol-global-value symbol new-value))
87 (declaim (inline %makunbound))
88 (defun %makunbound (symbol)
89 (%set-symbol-value symbol (%primitive sb!c:make-unbound-marker)))
91 (defun makunbound (symbol)
92 #!+sb-doc
93 "Make SYMBOL unbound, removing any value it may currently have."
94 (with-single-package-locked-error (:symbol symbol "unbinding the symbol ~A")
95 ;; :EVENTUALLY is allowed for :always-bound here, as it has no bearing
96 (when (eq (info :variable :always-bound symbol) :always-bound)
97 (error "Can't make ~A variable unbound: ~S" 'always-bound symbol))
98 (about-to-modify-symbol-value symbol 'makunbound)
99 (when (eq (info :variable :kind symbol) :constant)
100 (clear-info :variable :kind symbol))
101 (%makunbound symbol)
102 symbol))
104 ;; Compute a symbol's hash. Also used by FIND-SYMBOL which requires that a hash
105 ;; be a pure function of the name and not a semi-opaque property of the symbol.
106 ;; The hash of all symbols named "NIL" must be the same, so not to pessimize
107 ;; FIND-SYMBOL by special-casing the finding of CL:NIL with an extra "or"
108 ;; in the hash-equality test. i.e. We can't recognize that CL:NIL was the
109 ;; object sought (having an exceptional hash) until it has been found.
110 (defun compute-symbol-hash (string length)
111 (declare (simple-string string) (index length))
112 (if (and (= length 3)
113 (locally
114 ;; SXHASH-SUBSTRING is unsafe, so this is too. but do we know that
115 ;; length is ok, or is it an accident that it can scan too far?
116 (declare (optimize (safety 0)))
117 (string-dispatch (simple-base-string (simple-array character (*)))
118 string
119 (and (char= (schar string 0) #\N)
120 (char= (schar string 1) #\I)
121 (char= (schar string 2) #\L)))))
122 ;; FIXME: hardwire this. See similar comment at
123 ;; (deftransform sxhash ((x) (symbol))
124 (return-from compute-symbol-hash (symbol-hash nil)))
125 ;; And make a symbol's hash not the same as (sxhash name) in general.
126 (let ((sxhash (logand (lognot (%sxhash-simple-substring string length))
127 sb!xc:most-positive-fixnum)))
128 (if (zerop sxhash) #x55AA sxhash))) ; arbitrary substitute for 0
130 ;; Return SYMBOL's hash, a strictly positive fixnum, computing it if not stored.
131 ;; The inlined code for (SXHASH symbol) only calls ENSURE-SYMBOL-HASH if
132 ;; needed, however this is ok to call even if the hash is already nonzero.
133 (defun ensure-symbol-hash (symbol)
134 (let ((hash (symbol-hash symbol)))
135 (if (zerop hash)
136 (let ((name (symbol-name symbol)))
137 (%set-symbol-hash symbol (compute-symbol-hash name (length name))))
138 hash)))
140 ;;; Interpreter stub: Return whatever is in the SYMBOL-HASH slot of SYMBOL.
141 (defun symbol-hash (symbol)
142 (symbol-hash symbol))
144 (defun symbol-function (symbol)
145 #!+sb-doc
146 "Return SYMBOL's current function definition. Settable with SETF."
147 (%coerce-name-to-fun symbol symbol-fdefn))
149 ;; I think there are two bugs here.
150 ;; Per CLHS "SETF may be used with symbol-function to replace a global
151 ;; function definition when the symbol's function definition
152 ;; does not represent a special operator."
153 ;; 1. This should fail:
154 ;; * (in-package CL) ; circumvent package lock
155 ;; * (setf (symbol-function 'if) #'cons) => #<FUNCTION CONS>
156 ;; 2. (SETF (SYMBOL-FUNCTION 'I-ONCE-WAS-A-MACRO) #'CONS)
157 ;; should _probably_ make I-ONCE-WAS-A-MACRO not a macro
158 (defun (setf symbol-function) (new-value symbol)
159 (declare (type symbol symbol) (type function new-value))
160 ;; (SYMBOL-FUNCTION symbol) == (FDEFINITION symbol) according to the writeup
161 ;; on SYMBOL-FUNCTION. It doesn't say that SETF behaves the same, but let's
162 ;; assume it does, and that we can't assign our macro/special guard funs.
163 (err-if-unacceptable-function new-value '(setf symbol-function))
164 (with-single-package-locked-error
165 (:symbol symbol "setting the symbol-function of ~A")
166 ;; This code is a little "surprising" in that it is not just a limited
167 ;; case of (SETF FDEFINITION), but instead a different thing.
168 ;; I really think the code paths should be reconciled.
169 ;; e.g. what's up with *USER-HASH-TABLE-TESTS* being checked
170 ;; in %SET-FDEFINITION but not here?
171 (maybe-clobber-ftype symbol new-value)
172 (let ((fdefn (find-or-create-fdefn symbol)))
173 (setf (fdefn-fun fdefn) new-value))))
175 ;;; Accessors for the dual-purpose info/plist slot
177 ;; A symbol's INFO slot is always in one of three states:
178 ;; 1. NIL ; the initial state
179 ;; 2. #(data ....) ; globaldb used the slot
180 ;; 3. (PLIST . NIL) or (PLIST . #(data ...)) ; plist was touched,
181 ;; and also possibly globaldb used the slot
183 ;; State 1 transitions to state 2 by assigning globaldb data,
184 ;; or to state 3 via ({SETF|CAS} SYMBOL-PLIST).
185 ;; (SETF INFO) by itself will never cause 1 -> 3 transition.
186 ;; State 2 transitions to state 3 via ({SETF|CAS} SYMBOL-PLIST).
187 ;; There are *no* other permissible state transitions.
189 (defun symbol-info (symbol)
190 (symbol-info symbol))
192 ;; An "interpreter stub" for an operation that is only implemented for
193 ;; the benefit of platforms without compare-and-swap-vops.
194 (defun (setf symbol-info) (new-info symbol)
195 (setf (symbol-info symbol) new-info))
197 ;; Atomically update SYMBOL's info/plist slot to contain a new info vector.
198 ;; The vector is computed by calling UPDATE-FN on the old vector,
199 ;; repeatedly as necessary, until no conflict happens with other updaters.
200 ;; The function may choose to abort the update by returning NIL.
201 (defun update-symbol-info (symbol update-fn)
202 (declare (symbol symbol)
203 (type (function (t) t) update-fn))
204 (prog ((info-holder (symbol-info symbol))
205 (current-vect))
206 outer-restart
207 ;; Do not use SYMBOL-INFO-VECTOR - this must not perform a slot read again.
208 (setq current-vect (if (listp info-holder) (cdr info-holder) info-holder))
209 inner-restart
210 ;; KLUDGE: The "#." on +nil-packed-infos+ is due to slightly crippled
211 ;; fops in genesis's fasload. Anonymizing the constant works around the
212 ;; issue, at the expense of an extra copy of the empty info vector.
213 (let ((new-vect (funcall update-fn
214 (or current-vect #.+nil-packed-infos+))))
215 (unless (simple-vector-p new-vect)
216 (aver (null new-vect))
217 (return)) ; nothing to do
218 (if (consp info-holder) ; State 3: exchange the CDR
219 (let ((old (%compare-and-swap-cdr info-holder current-vect new-vect)))
220 (when (eq old current-vect) (return t)) ; win
221 (setq current-vect old) ; Don't touch holder- it's still a cons
222 (go inner-restart)))
223 ;; State 1 or 2: info-holder is NIL or a vector.
224 ;; Exchange the contents of the info slot. Type-inference derives
225 ;; SIMPLE-VECTOR-P on the args to CAS, so no extra checking.
226 (let ((old (%compare-and-swap-symbol-info symbol info-holder new-vect)))
227 (when (eq old info-holder) (return t)) ; win
228 ;; Check whether we're in state 2 or 3 now.
229 ;; Impossible to be in state 1: nobody ever puts NIL in the slot.
230 ;; Up above, we bailed out if the update-fn returned NIL.
231 (setq info-holder old)
232 (go outer-restart)))))
234 (eval-when (:compile-toplevel)
235 ;; If we're in state 1 or state 3, we can take (CAR (SYMBOL-INFO S))
236 ;; to get the property list. If we're in state 2, this same access
237 ;; gets the fixnum which is the VECTOR-LENGTH of the info vector.
238 ;; So all we have to do is turn any fixnum to NIL, and we have a plist.
239 ;; Ensure that this pun stays working.
240 (assert (= (- (* sb!vm:n-word-bytes sb!vm:cons-car-slot)
241 sb!vm:list-pointer-lowtag)
242 (- (* sb!vm:n-word-bytes sb!vm:vector-length-slot)
243 sb!vm:other-pointer-lowtag))))
245 (defun symbol-plist (symbol)
246 #!+sb-doc
247 "Return SYMBOL's property list."
248 #!+symbol-info-vops
249 (symbol-plist symbol) ; VOP translates it
250 #!-symbol-info-vops
251 (let ((list (car (truly-the list (symbol-info symbol))))) ; a white lie
252 ;; Just ensure the result is not a fixnum, and we're done.
253 (if (fixnump list) nil list)))
255 (declaim (ftype (sfunction (symbol t) cons) %ensure-plist-holder)
256 (inline %ensure-plist-holder))
258 ;; When a plist update (setf or cas) is first performed on a symbol,
259 ;; a one-time allocation of an extra cons is done which creates two
260 ;; "slots" from one: a slot for the info-vector and a slot for the plist.
261 ;; This avoids complications in the implementation of the user-facing
262 ;; (CAS SYMBOL-PLIST) function, which should not have to be aware of
263 ;; competition from globaldb mutators even if no other threads attempt
264 ;; to manipulate the plist per se.
266 ;; Given a SYMBOL and its current INFO of type (OR LIST SIMPLE-VECTOR)
267 ;; ensure that SYMBOL's current info is a cons, and return that.
268 ;; If racing with multiple threads, at most one thread will install the cons.
269 (defun %ensure-plist-holder (symbol info)
270 ;; Invoked only when SYMBOL is known to be a symbol.
271 (declare (optimize (safety 0)))
272 (if (consp info) ; it's fine to call this with a cell already installed
273 info ; all done
274 (let (newcell)
275 ;; The pointer from the new cons to the old info must be persisted
276 ;; to memory before the symbol's info slot points to the cons.
277 ;; [x86oid doesn't need the barrier, others might]
278 (sb!thread:barrier (:write)
279 (setq newcell (cons nil info)))
280 (loop (let ((old (%compare-and-swap-symbol-info symbol info newcell)))
281 (cond ((eq old info) (return newcell)) ; win
282 ((consp old) (return old))) ; somebody else made a cons!
283 (setq info old)
284 (sb!thread:barrier (:write) ; Retry using same newcell
285 (rplacd newcell info)))))))
287 (declaim (inline %compare-and-swap-symbol-plist
288 %set-symbol-plist))
290 (defun %compare-and-swap-symbol-plist (symbol old new)
291 ;; This is the entry point into which (CAS SYMBOL-PLIST) is transformed.
292 ;; If SYMBOL's info cell is a cons, we can do (CAS CAR). Otherwise punt.
293 (declare (symbol symbol) (list old new))
294 (let ((cell (symbol-info symbol)))
295 (if (consp cell)
296 (%compare-and-swap-car cell old new)
297 (%%compare-and-swap-symbol-plist symbol old new))))
299 (defun %%compare-and-swap-symbol-plist (symbol old new)
300 ;; This is just the second half of a partially-inline function, to avoid
301 ;; code bloat in the exceptional case. Type assertions should have been
302 ;; done - or not, per policy - by the caller of %COMPARE-AND-SWAP-SYMBOL-PLIST
303 ;; so now use TRULY-THE to avoid further type checking.
304 (%compare-and-swap-car (%ensure-plist-holder (truly-the symbol symbol)
305 (symbol-info symbol))
306 old new))
308 (defun %set-symbol-plist (symbol new-value)
309 ;; This is the entry point into which (SETF SYMBOL-PLIST) is transformed.
310 ;; If SYMBOL's info cell is a cons, we can do (SETF CAR). Otherwise punt.
311 (declare (symbol symbol) (list new-value))
312 (let ((cell (symbol-info symbol)))
313 (if (consp cell)
314 (setf (car cell) new-value)
315 (%%set-symbol-plist symbol new-value))))
317 (defun %%set-symbol-plist (symbol new-value)
318 ;; Same considerations as for %%COMPARE-AND-SWAP-SYMBOL-PLIST,
319 ;; with a slight efficiency hack: if the symbol has no plist holder cell
320 ;; and the NEW-VALUE is NIL, try to avoid creating a holder cell.
321 ;; Yet we must write something, because omitting a memory operation
322 ;; could have a subtle effect in the presence of multi-threading.
323 (let ((info (symbol-info (truly-the symbol symbol))))
324 (when (and (not new-value) (atom info)) ; try to treat this as a no-op
325 (let ((old (%compare-and-swap-symbol-info symbol info info)))
326 (if (eq old info) ; good enough
327 (return-from %%set-symbol-plist new-value) ; = nil
328 (setq info old))))
329 (setf (car (%ensure-plist-holder symbol info)) new-value)))
331 ;;; End of Info/Plist slot manipulation
333 (defun symbol-name (symbol)
334 #!+sb-doc
335 "Return SYMBOL's name as a string."
336 (symbol-name symbol))
338 (defun symbol-package (symbol)
339 #!+sb-doc
340 "Return the package SYMBOL was interned in, or NIL if none."
341 (symbol-package symbol))
343 (defun %set-symbol-package (symbol package)
344 (declare (type symbol symbol))
345 (%set-symbol-package symbol package))
347 (defun make-symbol (string)
348 #!+sb-doc
349 "Make and return a new symbol with the STRING as its print name."
350 (declare (type string string))
351 (%make-symbol (if (simple-string-p string)
352 string
353 (subseq string 0))))
355 (defun get (symbol indicator &optional (default nil))
356 #!+sb-doc
357 "Look on the property list of SYMBOL for the specified INDICATOR. If this
358 is found, return the associated value, else return DEFAULT."
359 (get3 symbol indicator default))
361 (defun get3 (symbol indicator default)
362 (let (cdr-pl)
363 (do ((pl (symbol-plist symbol) (cdr cdr-pl)))
364 ((atom pl) default)
365 (setq cdr-pl (cdr pl))
366 (cond ((atom cdr-pl)
367 (error "~S has an odd number of items in its property list."
368 symbol))
369 ((eq (car pl) indicator)
370 (return (car cdr-pl)))))))
372 (defun %put (symbol indicator value)
373 #!+sb-doc
374 "The VALUE is added as a property of SYMBOL under the specified INDICATOR.
375 Returns VALUE."
376 (do ((pl (symbol-plist symbol) (cddr pl)))
377 ((endp pl)
378 (setf (symbol-plist symbol)
379 (list* indicator value (symbol-plist symbol)))
380 value)
381 (cond ((endp (cdr pl))
382 (error "~S has an odd number of items in its property list."
383 symbol))
384 ((eq (car pl) indicator)
385 (rplaca (cdr pl) value)
386 (return value)))))
388 (defun remprop (symbol indicator)
389 #!+sb-doc
390 "Look on property list of SYMBOL for property with specified
391 INDICATOR. If found, splice this indicator and its value out of
392 the plist, and return the tail of the original list starting with
393 INDICATOR. If not found, return () with no side effects.
395 NOTE: The ANSI specification requires REMPROP to return true (not false)
396 or false (the symbol NIL). Portable code should not rely on any other value."
397 (do ((pl (symbol-plist symbol) (cddr pl))
398 (prev nil pl))
399 ((atom pl) nil)
400 (cond ((atom (cdr pl))
401 (error "~S has an odd number of items in its property list."
402 symbol))
403 ((eq (car pl) indicator)
404 (cond (prev (rplacd (cdr prev) (cddr pl)))
406 (setf (symbol-plist symbol) (cddr pl))))
407 (return pl)))))
409 (defun getf (place indicator &optional (default ()))
410 #!+sb-doc
411 "Search the property list stored in PLACE for an indicator EQ to INDICATOR.
412 If one is found, return the corresponding value, else return DEFAULT."
413 (do ((plist place (cddr plist)))
414 ((null plist) default)
415 (cond ((atom (cdr plist))
416 (error 'simple-type-error
417 :format-control "malformed property list: ~S."
418 :format-arguments (list place)
419 :datum (cdr plist)
420 :expected-type 'cons))
421 ((eq (car plist) indicator)
422 (return (cadr plist))))))
424 (defun %putf (place property new-value)
425 (declare (type list place))
426 (do ((plist place (cddr plist)))
427 ((endp plist) (list* property new-value place))
428 (declare (type list plist))
429 (when (eq (car plist) property)
430 (setf (cadr plist) new-value)
431 (return place))))
433 (defun get-properties (place indicator-list)
434 #!+sb-doc
435 "Like GETF, except that INDICATOR-LIST is a list of indicators which will
436 be looked for in the property list stored in PLACE. Three values are
437 returned, see manual for details."
438 (do ((plist place (cddr plist)))
439 ((null plist) (values nil nil nil))
440 (cond ((atom (cdr plist))
441 (error 'simple-type-error
442 :format-control "malformed property list: ~S."
443 :format-arguments (list place)
444 :datum (cdr plist)
445 :expected-type 'cons))
446 ((memq (car plist) indicator-list)
447 (return (values (car plist) (cadr plist) plist))))))
449 (defun copy-symbol (symbol &optional (copy-props nil) &aux new-symbol)
450 #!+sb-doc
451 "Make and return a new uninterned symbol with the same print name
452 as SYMBOL. If COPY-PROPS is false, the new symbol is neither bound
453 nor fbound and has no properties, else it has a copy of SYMBOL's
454 function, value and property list."
455 (declare (type symbol symbol))
456 (setq new-symbol (make-symbol (symbol-name symbol)))
457 (when copy-props
458 (%set-symbol-value new-symbol
459 (%primitive sb!c:fast-symbol-value symbol))
460 (setf (symbol-plist new-symbol)
461 (copy-list (symbol-plist symbol)))
462 (when (fboundp symbol)
463 (setf (symbol-function new-symbol) (symbol-function symbol))))
464 new-symbol)
466 (defun keywordp (object)
467 #!+sb-doc
468 "Return true if Object is a symbol in the \"KEYWORD\" package."
469 (and (symbolp object)
470 (eq (symbol-package object) *keyword-package*)))
472 ;;;; GENSYM and friends
474 (defun %make-symbol-name (prefix counter)
475 (declare (string prefix))
476 (if (typep counter '(and fixnum unsigned-byte))
477 (let ((s ""))
478 (declare (simple-string s))
479 (labels ((recurse (depth n)
480 (multiple-value-bind (q r) (truncate n 10)
481 (if (plusp q)
482 (recurse (1+ depth) q)
483 (let ((et (if (or (base-string-p prefix)
484 #!+sb-unicode ; no #'base-char-p
485 (every #'base-char-p prefix))
486 'base-char 'character)))
487 (setq s (make-string (+ (length prefix) depth)
488 :element-type et))
489 (replace s prefix)))
490 (setf (char s (- (length s) depth))
491 (code-char (+ (char-code #\0) r)))
492 s)))
493 (recurse 1 counter)))
494 (with-simple-output-to-string (s)
495 (write-string prefix s)
496 (%output-integer-in-base counter 10 s))))
498 (defvar *gensym-counter* 0
499 #!+sb-doc
500 "counter for generating unique GENSYM symbols")
501 (declaim (type unsigned-byte *gensym-counter*))
503 (defun gensym (&optional (thing "G"))
504 #!+sb-doc
505 "Creates a new uninterned symbol whose name is a prefix string (defaults
506 to \"G\"), followed by a decimal number. Thing, when supplied, will
507 alter the prefix if it is a string, or be used for the decimal number
508 if it is a number, of this symbol. The default value of the number is
509 the current value of *gensym-counter* which is incremented each time
510 it is used."
511 (multiple-value-bind (prefix int)
512 (if (integerp thing)
513 (values "G" thing)
514 (values thing (let ((old *gensym-counter*))
515 (setq *gensym-counter* (1+ old))
516 old)))
517 (make-symbol (%make-symbol-name prefix int))))
519 (defvar *gentemp-counter* 0)
520 (declaim (type unsigned-byte *gentemp-counter*))
522 (defun gentemp (&optional (prefix "T") (package (sane-package)))
523 #!+sb-doc
524 "Creates a new symbol interned in package PACKAGE with the given PREFIX."
525 (declare (type string prefix))
526 (loop for name = (%make-symbol-name prefix (incf *gentemp-counter*))
527 while (nth-value 1 (find-symbol name package))
528 finally (return (values (intern name package)))))
530 ;;; This function is to be called just before a change which would affect the
531 ;;; symbol value. We don't absolutely have to call this function before such
532 ;;; changes, since such changes to constants are given as undefined behavior,
533 ;;; it's nice to do so. To circumvent this you need code like this:
535 ;;; (defvar foo)
536 ;;; (defun set-foo (x) (setq foo x))
537 ;;; (defconstant foo 42)
538 ;;; (set-foo 13)
539 ;;; foo => 13, (constantp 'foo) => t
541 ;;; ...in which case you frankly deserve to lose.
542 (defun about-to-modify-symbol-value (symbol action &optional (new-value nil valuep) bind)
543 (declare (symbol symbol))
544 (declare (explicit-check))
545 (flet ((describe-action ()
546 (ecase action
547 (set "set SYMBOL-VALUE of ~S")
548 (progv "bind ~S")
549 (compare-and-swap "compare-and-swap SYMBOL-VALUE of ~S")
550 (defconstant "define ~S as a constant")
551 (makunbound "make ~S unbound"))))
552 (let ((kind (info :variable :kind symbol)))
553 (multiple-value-bind (what continue)
554 (cond ((eq :constant kind)
555 (cond ((eq symbol t)
556 (values "Veritas aeterna. (can't ~@?)" nil))
557 ((eq symbol nil)
558 (values "Nihil ex nihil. (can't ~@?)" nil))
559 ((keywordp symbol)
560 (values "Can't ~@?." nil))
562 (values "Constant modification: attempt to ~@?." t))))
563 ((and bind (eq :global kind))
564 (values "Can't ~@? (global variable)." nil)))
565 (when what
566 (if continue
567 (cerror "Modify the constant." what (describe-action) symbol)
568 (error what (describe-action) symbol)))
569 (when valuep
570 (multiple-value-bind (type declaredp) (info :variable :type symbol)
571 ;; If globaldb returned the default of *UNIVERSAL-TYPE*,
572 ;; don't bother with a type test.
573 (when (and declaredp (not (%%typep new-value type nil)))
574 (let ((spec (type-specifier type)))
575 (error 'simple-type-error
576 :format-control "~@<Cannot ~@? to ~S, not of type ~S.~:@>"
577 :format-arguments (list (describe-action) symbol new-value spec)
578 :datum new-value
579 :expected-type spec)))))))
580 nil))