%other-pointer-widetag derive-type: derive for simple-array.
[sbcl.git] / src / code / target-error.lisp
blob6e4375d5c6eb653e816656b850b5313c18c354c4
1 ;;;; that part of the condition system which can or should come early
2 ;;;; (mostly macro-related)
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
13 (in-package "SB-KERNEL")
15 (declaim (global *type-system-initialized*))
17 (defun decode-internal-error-args (sap trap-number &optional error-number)
18 (let ((error-number (cond (error-number)
19 ((>= trap-number sb-vm:error-trap)
20 (prog1
21 (- trap-number sb-vm:error-trap)
22 (setf trap-number sb-vm:error-trap)))
24 (prog1 (sap-ref-8 sap 0)
25 (setf sap (sap+ sap 1)))))))
26 (let ((length (error-length error-number)))
27 (declare (type (unsigned-byte 8) length))
28 (values error-number
29 (loop with index = 0
30 repeat length
31 collect (sb-c:sap-read-var-integerf sap index))
32 trap-number))))
34 (defun muffle-warning-p (warning)
35 (declare (special *muffled-warnings*))
36 (typep warning *muffled-warnings*))
38 ;;; Each cluster is an alist of the form
39 ;;;
40 ;;; ((TYPE-TEST1 . HANDLER1) (TYPE-TEST2 . HANDLER2) ...)
41 ;;;
42 ;;; where TYPE-TESTN are functions of one argument which test a given
43 ;;; condition instance for the type required by the corresponding
44 ;;; HANDLERN. HANDLERN are function designators.
45 ;;;
46 ;;; Newly established handlers are added at the beginning of the
47 ;;; list. Elements to the left of the alist take precedence over
48 ;;; elements to the right.
49 ;;;
50 ;;; Lists to which *HANDLER-CLUSTERS* is bound generally have dynamic
51 ;;; extent.
53 (defmethod print-object ((restart restart) stream)
54 (if *print-escape*
55 (print-unreadable-object (restart stream :type t :identity t)
56 (prin1 (restart-name restart) stream))
57 (restart-report restart stream)))
59 (setf (documentation 'restart-name 'function)
60 "Return the name of the given restart object.")
62 (defun restart-report (restart stream)
63 (if (restart-report-function restart)
64 (funcall (truly-the function (restart-report-function restart))
65 stream)
66 (prin1 (or (restart-name restart)
67 restart)
68 stream)))
70 (defvar *restart-test-stack* nil)
72 ;; Call FUNCTION with all restarts in the current dynamic environment,
73 ;; 1) that are associated to CONDITION (when CONDITION is NIL, all
74 ;; restarts are processed)
75 ;; 2) and for which the restart test returns non-NIL for CONDITION.
76 ;; When CALL-TEST-P is non-NIL, all restarts are processed.
77 (defun map-restarts (function &optional condition (call-test-p t))
78 (declare (function function))
79 (let ((stack *restart-test-stack*))
80 (dolist (restart-cluster *restart-clusters*)
81 (dolist (restart restart-cluster)
82 (when (and (or (not condition)
83 (null (restart-associated-conditions restart))
84 (memq condition (restart-associated-conditions restart)))
85 ;; A call to COMPUTE-RESTARTS -- from an error,
86 ;; from user code, whatever -- inside the test
87 ;; function would cause infinite recursion here, so
88 ;; we disable each restart using
89 ;; *restart-test-stack* for the duration of the
90 ;; test call.
91 (not (memq restart stack))
92 (or (not call-test-p)
93 (let ((*restart-test-stack* (cons restart stack)))
94 (declare (dynamic-extent *restart-test-stack*))
95 (funcall (restart-test-function restart) condition))))
96 (funcall function restart))))))
98 (defun compute-restarts (&optional condition)
99 "Return a list of all the currently active restarts ordered from most recently
100 established to less recently established. If CONDITION is specified, then only
101 restarts associated with CONDITION (or with no condition) will be returned."
102 (collect ((result))
103 (map-restarts (lambda (restart) (result restart)) condition)
104 (result)))
106 (defun %find-restart (identifier condition &optional (call-test-p t))
107 (flet ((eq-restart-p (restart)
108 (when (eq identifier restart)
109 (return-from %find-restart restart)))
110 (named-restart-p (restart)
111 (when (eq identifier (restart-name restart))
112 (return-from %find-restart restart))))
113 ;; KLUDGE: can the compiler infer this dx automatically?
114 (declare (dynamic-extent #'eq-restart-p #'named-restart-p))
115 (if (typep identifier 'restart)
116 ;; The code under #+previous-... below breaks the abstraction
117 ;; introduced by MAP-RESTARTS, but is about twice as
118 ;; fast as #+equivalent-... . Also, it is a common case due to
120 ;; (INVOKE-RESTART RESTART)
121 ;; -> (FIND-RESTART-OR-CONTROL-ERROR RESTART)
122 ;; -> (FIND-RESTART RESTART)
124 ;; However, both #+previous-... and #+equivalent-... may be
125 ;; wrong altogether because of
126 ;; https://bugs.launchpad.net/sbcl/+bug/774410:
127 ;; The behavior expected in that report can be achieved by the
128 ;; following line (which is, of course, the slowest of all
129 ;; possibilities):
130 (map-restarts #'eq-restart-p condition call-test-p)
132 #+equivalent-to-previous-sbcl-behavior--faster-but-see-bug-774410
133 (map-restarts #'eq-restart-p nil nil)
135 #+previous-behavior--fastest-but-see-bug-774410
136 (and (find-if (lambda (cluster) (find identifier cluster)) *restart-clusters*)
137 identifier)
139 (map-restarts #'named-restart-p condition call-test-p))))
141 (defun find-restart (identifier &optional condition)
142 "Return the first restart identified by IDENTIFIER. If IDENTIFIER is a symbol,
143 then the innermost applicable restart with that name is returned. If IDENTIFIER
144 is a restart, it is returned if it is currently active. Otherwise NIL is
145 returned. If CONDITION is specified and not NIL, then only restarts associated
146 with that condition (or with no condition) will be returned."
147 ;; Calls MAP-RESTARTS such that restart test functions are
148 ;; respected.
149 (%find-restart identifier condition))
151 ;;; helper for the various functions which are ANSI-spec'ed to do
152 ;;; something with a restart or signal CONTROL-ERROR if there is none
153 (define-error-wrapper find-restart-or-control-error (identifier &optional condition (call-test-p t))
154 (or (%find-restart identifier condition call-test-p)
155 (error 'simple-control-error
156 :format-control "No restart ~S is active~@[ for ~S~]."
157 :format-arguments (list identifier condition))))
159 (defun invoke-restart (restart &rest values)
160 "Calls the function associated with the given restart, passing any given
161 arguments. If the argument restart is not a restart or a currently active
162 non-nil restart name, then a CONTROL-ERROR is signalled."
163 (/show "entering INVOKE-RESTART" restart)
164 ;; The following code calls MAP-RESTARTS (through
165 ;; FIND-RESTART-OR-CONTROL-ERROR -> %FIND-RESTART) such that restart
166 ;; test functions are respected when RESTART is a symbol, but not
167 ;; when RESTART is a RESTART instance.
169 ;; Without disabling test functions for the RESTART instance case,
170 ;; the following problem would arise:
172 ;; (restart-case
173 ;; (handler-bind
174 ;; ((some-condition (lambda (c)
175 ;; (invoke-restart (find-restart 'foo c)) ; a)
176 ;; (invoke-restart 'foo) ; b)
177 ;; )))
178 ;; (signal 'some-condition))
179 ;; (foo ()
180 ;; :test (lambda (c) (typep c 'some-condition))))
182 ;; In case a), INVOKE-RESTART receives the RESTART instance, but
183 ;; cannot supply the condition instance needed by the test. In case
184 ;; b) INVOKE-RESTART calls FIND-RESTART, but again cannot supply the
185 ;; condition instance. As a result, the restart would be impossible
186 ;; the invoke.
187 (let ((real-restart (find-restart-or-control-error
188 restart nil (symbolp restart))))
189 (apply (restart-function real-restart) values)))
191 (defun interactive-restart-arguments (real-restart)
192 (let ((interactive-function (restart-interactive-function real-restart)))
193 (if interactive-function
194 (funcall interactive-function)
195 '())))
197 (defun invoke-restart-interactively (restart)
198 "Calls the function associated with the given restart, prompting for any
199 necessary arguments. If the argument restart is not a restart or a
200 currently active non-NIL restart name, then a CONTROL-ERROR is signalled."
201 ;; For an explanation of the call to FIND-RESTART-OR-CONTROL-ERROR,
202 ;; see comment in INVOKE-RESTART.
203 (let* ((real-restart (find-restart-or-control-error
204 restart nil (symbolp restart)))
205 (args (interactive-restart-arguments real-restart)))
206 (apply (restart-function real-restart) args)))
208 ;;; To reduce expansion size of RESTART-CASE
209 (defun with-simple-condition-restarts (function cerror-arg datum &rest arguments)
210 (let ((sb-debug:*stack-top-hint* (or sb-debug:*stack-top-hint*
211 'with-simple-condition-restarts))
212 (condition (apply #'coerce-to-condition datum
213 (case function
214 (warn 'simple-warning)
215 (signal 'simple-condition)
216 (t 'simple-error))
217 function
218 arguments)))
219 (with-condition-restarts condition (car *restart-clusters*)
220 (if (eq function 'cerror)
221 (cerror cerror-arg condition)
222 (funcall function condition)))))
225 ;;;; Conditions.
227 (!defstruct-with-alternate-metaclass condition
228 :slot-names (assigned-slots)
229 :constructor nil
230 :superclass-name t
231 :metaclass-name condition-classoid
232 :metaclass-constructor make-condition-classoid
233 :dd-type structure)
235 ;;; Needed for !CALL-A-METHOD to pick out CONDITIONs
236 (defun !condition-p (x) (typep x 'condition))
238 (defstruct (condition-slot (:copier nil))
239 (name (missing-arg) :type symbol)
240 ;; list of all applicable initargs
241 (initargs (missing-arg) :type list)
242 ;; names of reader and writer functions
243 (readers (missing-arg) :type list)
244 (writers (missing-arg) :type list)
245 ;; true if :INITFORM was specified
246 (initform-p (missing-arg) :type (member t nil))
247 ;; the initform if :INITFORM was specified, otherwise NIL
248 (initform nil :type t)
249 ;; if this is a function, call it with no args to get the initform value
250 (initfunction (missing-arg) :type t)
251 ;; allocation of this slot, or NIL until defaulted
252 (allocation nil :type (member :instance :class nil))
253 ;; If ALLOCATION is :CLASS, this is a cons whose car holds the value
254 (cell nil :type (or cons null))
255 ;; slot documentation
256 (documentation nil :type (or string null)))
258 (eval-when (:compile-toplevel :load-toplevel :execute)
259 (let ((condition-class (find-classoid 'condition)))
260 (setf (condition-classoid-cpl condition-class)
261 (list condition-class))))
263 (setf (condition-classoid-report (find-classoid 'condition))
264 (lambda (cond stream)
265 (format stream "Condition ~/sb-impl:print-type-specifier/ was signalled."
266 (type-of cond))))
268 (eval-when (:compile-toplevel :load-toplevel :execute)
270 (defun find-condition-layout (name parent-types)
271 (let* ((cpl (remove-duplicates
272 (reverse
273 (reduce #'append
274 (mapcar (lambda (x)
275 (condition-classoid-cpl
276 (find-classoid x)))
277 parent-types)))))
278 (cond-layout (info :type :compiler-layout 'condition))
279 (olayout (info :type :compiler-layout name))
280 ;; FIXME: Does this do the right thing in case of multiple
281 ;; inheritance? A quick look at DEFINE-CONDITION didn't make
282 ;; it obvious what ANSI intends to be done in the case of
283 ;; multiple inheritance, so it's not actually clear what the
284 ;; right thing is..
285 (new-inherits
286 (order-layout-inherits (concatenate 'simple-vector
287 (layout-inherits cond-layout)
288 (mapcar #'classoid-layout cpl)))))
289 (if (and olayout
290 (not (mismatch (layout-inherits olayout) new-inherits)))
291 olayout
292 ;; All condition classoid layouts carry the same LAYOUT-INFO - the defstruct
293 ;; description for CONDITION - which is a representation of the primitive object
294 ;; and not the lisp-level object.
295 (make-layout (hash-layout-name name)
296 (make-undefined-classoid name)
297 :info (layout-info cond-layout)
298 :flags (logior +condition-layout-flag+ +strictly-boxed-flag+)
299 :inherits new-inherits
300 :depthoid -1
301 :length (layout-length cond-layout)))))
303 ) ; EVAL-WHEN
306 ;;;; slots of CONDITION objects
308 (defun find-slot-default (condition classoid slot &optional boundp)
309 (multiple-value-bind (value found) (find-slot-default-initarg classoid slot)
310 ;; When CLASSOID or a superclass has a default initarg for SLOT, use
311 ;; that.
312 (cond (found
313 value)
314 ;; Otherwise use the initform of SLOT, if there is one.
315 ((condition-slot-initform-p slot)
316 (let ((initfun (condition-slot-initfunction slot)))
317 (aver (functionp initfun))
318 (funcall initfun)))
319 ;; if we're computing SLOT-BOUNDP, return an unbound marker
320 (boundp sb-pcl:+slot-unbound+)
321 ;; if we're computing SLOT-VALUE, call SLOT-UNBOUND
323 (let ((class (classoid-pcl-class classoid))
324 (name (condition-slot-name slot)))
325 (values (slot-unbound class condition name)))))))
327 (defun find-slot-default-initarg (classoid slot)
328 (let ((initargs (condition-slot-initargs slot))
329 (cpl (condition-classoid-cpl classoid)))
330 (dolist (classoid cpl)
331 (let ((direct-default-initargs
332 (condition-classoid-direct-default-initargs classoid)))
333 (dolist (initarg initargs)
334 (let ((initfunction (third (assoc initarg direct-default-initargs))))
335 (when initfunction
336 (return-from find-slot-default-initarg
337 (values (funcall initfunction) t)))))))
338 (values nil nil)))
340 (defun find-condition-class-slot (condition-class slot-name)
341 (dolist (sclass
342 (condition-classoid-cpl condition-class)
343 (error "There is no slot named ~S in ~S."
344 slot-name condition-class))
345 (dolist (slot (condition-classoid-slots sclass))
346 (when (eq (condition-slot-name slot) slot-name)
347 (return-from find-condition-class-slot slot)))))
349 ;;;; MAKE-CONDITION
351 ;;; Pre-scan INITARGS to see whether any are stack-allocated.
352 ;;; If not, then life is easy. If any are, then depending on whether the
353 ;;; condition is a TYPE-ERROR, call TYPE-OF on the bad datum, so that
354 ;;; if the condition outlives the extent of the object, and someone tries
355 ;;; to print the condition, we don't crash.
356 ;;; Putting a placeholder in for the datum would work, but seems a bit evil,
357 ;;; since the user might actually want to know what it was. And we shouldn't
358 ;;; assume that the object would definitely escape its dynamic-extent.
360 (defun allocate-condition (designator &rest initargs)
361 (when (oddp (length initargs))
362 (error 'simple-error
363 :format-control "odd-length initializer list: ~S."
364 ;; Passing the initargs to LIST avoids consing them into
365 ;; a list except when this error is signaled.
366 :format-arguments (list (apply #'list initargs))))
367 ;; I am going to assume that people are not somehow getting to here
368 ;; with a CLASSOID, which is not strictly legal as a designator,
369 ;; but which is accepted because it is actually the desired thing.
370 ;; It doesn't seem worth sweating over that detail, and in any event
371 ;; we could say that it's a supported extension.
372 (let ((classoid (named-let lookup ((designator designator))
373 (typecase designator
374 (symbol (find-classoid designator nil))
375 (class (lookup (class-name designator)))
376 (t designator)))))
377 (unless (condition-classoid-p classoid)
378 (error 'simple-type-error
379 :datum designator
380 :expected-type 'sb-pcl::condition-class
381 :format-control "~S does not designate a condition class."
382 :format-arguments (list designator)))
383 (flet ((stream-err-p (layout)
384 (let ((stream-err-layout (load-time-value (find-layout 'stream-error))))
385 (or (eq layout stream-err-layout)
386 (find stream-err-layout (layout-inherits layout)))))
387 (type-err-p (layout)
388 (let ((type-err-layout (load-time-value (find-layout 'type-error))))
389 (or (eq layout type-err-layout)
390 (find type-err-layout (layout-inherits layout)))))
391 ;; avoid full calls to STACK-ALLOCATED-P here
392 (stackp (x)
393 (let ((addr (get-lisp-obj-address x)))
394 (and (sb-vm:is-lisp-pointer addr)
395 (<= (get-lisp-obj-address sb-vm:*control-stack-start*) addr)
396 (< addr (get-lisp-obj-address sb-vm:*control-stack-end*))))))
397 (let* ((any-dx
398 (loop for arg-index from 1 below (length initargs) by 2
399 thereis (stackp (fast-&rest-nth arg-index initargs))))
400 (layout (classoid-layout classoid))
401 (extra (if (and any-dx (type-err-p layout)) 2 0)) ; space for secret initarg
402 (instance (%new-instance layout
403 (+ sb-vm:instance-data-start
404 1 ; ASSIGNED-SLOTS
405 (length initargs)
406 extra)))
407 (data-index (1+ sb-vm:instance-data-start))
408 (arg-index 0)
409 (have-type-error-datum)
410 (type-error-datum))
411 (setf (condition-assigned-slots instance) nil)
412 (macrolet ((store-pair (key val)
413 `(progn (%instance-set instance data-index ,key)
414 (%instance-set instance (1+ data-index) ,val))))
415 (cond ((not any-dx)
416 ;; uncomplicated way
417 (loop (when (>= arg-index (length initargs)) (return))
418 (store-pair (fast-&rest-nth arg-index initargs)
419 (fast-&rest-nth (1+ arg-index) initargs))
420 (incf data-index 2)
421 (incf arg-index 2)))
423 (loop (when (>= arg-index (length initargs)) (return))
424 (let ((key (fast-&rest-nth arg-index initargs))
425 (val (fast-&rest-nth (1+ arg-index) initargs)))
426 (when (and (eq key :datum)
427 (not have-type-error-datum)
428 (type-err-p layout))
429 (setq type-error-datum val
430 have-type-error-datum t))
431 (if (and (eq key :stream) (stream-err-p layout) (stackp val))
432 (store-pair key (sb-impl::make-stub-stream val))
433 (store-pair key val)))
434 (incf data-index 2)
435 (incf arg-index 2))
436 (when (and have-type-error-datum (/= extra 0))
437 ;; We can get into serious trouble here if the
438 ;; datum is already stack garbage!
439 (let ((actual-type (type-of type-error-datum)))
440 (store-pair 'dx-object-type actual-type))))))
441 (values instance classoid)))))
443 ;;; Access the type of type-error-datum if the datum can't be accessed.
444 ;;; Testing the stack pointer when rendering the condition is a heuristic
445 ;;; that might work, but more likely, the erring frame has been exited
446 ;;; and then the stack pointer changed again to make it seems like the
447 ;;; object pointer is valid. I'm not sure what to do, but we can leave
448 ;;; that decision for later.
449 (defun type-error-datum-stored-type (condition)
450 (do ((i (- (%instance-length condition) 2) (- i 2)))
451 ((<= i (1+ sb-vm:instance-data-start))
452 (make-unbound-marker))
453 (when (eq (%instance-ref condition i) 'dx-object-type)
454 (return (%instance-ref condition (1+ i))))))
456 (defun make-condition (type &rest initargs)
457 "Make an instance of a condition object using the specified initargs."
458 ;; Note: While ANSI specifies no exceptional situations in this function,
459 ;; ALLOCATE-CONDITION will signal a type error if TYPE does not designate
460 ;; a condition class. This seems fair enough.
461 (declare (explicit-check))
462 ;; FIXME: the compiler should have a way to make GETF operate on a &MORE arg
463 ;; so that the initargs are never listified.
464 (declare (dynamic-extent initargs))
465 (multiple-value-bind (condition classoid)
466 (apply #'allocate-condition type initargs)
468 ;; Set any class slots with initargs present in this call.
469 (dolist (cslot (condition-classoid-class-slots classoid))
470 (loop for (key value) on initargs by #'cddr
471 when (memq key (condition-slot-initargs cslot))
472 do (setf (car (condition-slot-cell cslot)) value)
473 (return)
474 finally
475 (multiple-value-bind (value found)
476 (find-slot-default-initarg classoid cslot)
477 (when found
478 (setf (car (condition-slot-cell cslot)) value)))))
480 ;; Default any slots with non-constant defaults now.
481 (dolist (hslot (condition-classoid-hairy-slots classoid))
482 (when (dolist (initarg (condition-slot-initargs hslot) t)
483 (unless (unbound-marker-p (getf initargs initarg sb-pcl:+slot-unbound+))
484 (return nil)))
485 (push (cons (condition-slot-name hslot)
486 (find-slot-default condition classoid hslot))
487 (condition-assigned-slots condition))))
489 condition))
491 ;;;; DEFINE-CONDITION
493 (define-load-time-global *define-condition-hooks* nil)
495 (defun %set-condition-report (name report)
496 (setf (condition-classoid-report (find-classoid name))
497 report))
499 ;;; Early definitions of slot accessor creators.
501 ;;; Slot accessors must be generic functions, but ANSI does not seem
502 ;;; to specify any of them, and we cannot support it before end of
503 ;;; warm init. So we use ordinary functions inside SBCL, and switch to
504 ;;; GFs only at the end of building.
505 (declaim (notinline install-condition-slot-reader
506 install-condition-slot-writer))
507 (defun install-condition-slot-reader (name condition slot-name)
508 (declare (ignore condition))
509 (setf (fdefinition name)
510 (set-closure-name
511 (lambda (condition) (condition-slot-value condition slot-name))
513 `(condition-slot-reader ,name))))
514 (defun install-condition-slot-writer (name condition slot-name)
515 (declare (ignore condition))
516 (setf (fdefinition name)
517 (set-closure-name
518 (lambda (new-value condition)
519 (set-condition-slot-value condition new-value slot-name))
521 `(condition-slot-writer ,name))))
523 (eval-when (:compile-toplevel :load-toplevel :execute)
524 (defun %%compiler-define-condition (name direct-supers layout readers writers)
525 (declare (notinline find-classoid))
526 (preinform-compiler-about-class-type name nil)
527 (preinform-compiler-about-accessors 'condition readers writers)
528 (multiple-value-bind (class old-layout)
529 (insured-find-classoid name
530 #'condition-classoid-p
531 #'make-condition-classoid)
532 (setf (layout-classoid layout) class)
533 (setf (classoid-direct-superclasses class)
534 (mapcar #'find-classoid direct-supers))
535 (cond ((not old-layout)
536 (register-layout layout))
537 ((not *type-system-initialized*)
538 (setf (layout-classoid old-layout) class)
539 (setq layout old-layout)
540 (unless (eq (classoid-layout class) layout)
541 (register-layout layout)))
542 ((warn-if-altered-layout "current"
543 old-layout
544 "new"
545 (layout-length layout)
546 (layout-inherits layout)
547 (layout-depthoid layout)
548 (layout-bitmap layout))
549 (register-layout layout :invalidate t))
550 ((not (classoid-layout class))
551 (register-layout layout)))
553 (setf (find-classoid name) class)
555 ;; Initialize CPL slot.
556 (setf (condition-classoid-cpl class)
557 (remove-if-not #'condition-classoid-p
558 (std-compute-class-precedence-list class)))))
560 (defun %compiler-define-condition (name direct-supers layout readers writers)
561 (call-with-defining-class
562 'condition name
563 (lambda ()
564 (%%compiler-define-condition name direct-supers layout readers writers))))
565 ) ; EVAL-WHEN
567 (defun %define-condition (name parent-types layout slots
568 direct-default-initargs all-readers all-writers
569 source-location &optional documentation)
570 (call-with-defining-class
571 'condition name
572 (lambda ()
573 (%%compiler-define-condition name parent-types layout all-readers all-writers)
574 (let ((classoid (find-classoid name)))
575 (when source-location
576 (setf (classoid-source-location classoid) source-location))
577 (setf (condition-classoid-slots classoid) slots
578 (condition-classoid-direct-default-initargs classoid) direct-default-initargs
579 (documentation name 'type) documentation)
581 (dolist (slot slots)
582 ;; Set up reader and writer functions.
583 (let ((slot-name (condition-slot-name slot)))
584 (dolist (reader (condition-slot-readers slot))
585 (install-condition-slot-reader reader name slot-name))
586 (dolist (writer (condition-slot-writers slot))
587 (install-condition-slot-writer writer name slot-name))))
589 ;; Compute effective slots and set up the class and hairy slots
590 ;; (subsets of the effective slots.)
591 (setf (condition-classoid-class-slots classoid) '()
592 (condition-classoid-hairy-slots classoid) '())
593 (let ((eslots (compute-effective-slots classoid))
594 (e-def-initargs
595 (reduce #'append
596 (mapcar #'condition-classoid-direct-default-initargs
597 (condition-classoid-cpl classoid)))))
598 (dolist (slot eslots)
599 (ecase (condition-slot-allocation slot)
600 (:class
601 (unless (condition-slot-cell slot)
602 (setf (condition-slot-cell slot)
603 (list (if (condition-slot-initform-p slot)
604 (let ((initfun (condition-slot-initfunction slot)))
605 (aver (functionp initfun))
606 (funcall initfun))
607 sb-pcl:+slot-unbound+))))
608 (push slot (condition-classoid-class-slots classoid)))
609 ((:instance nil)
610 (setf (condition-slot-allocation slot) :instance)
611 ;; FIXME: isn't this "always hairy"?
612 (when (or (functionp (condition-slot-initfunction slot))
613 (dolist (initarg (condition-slot-initargs slot) nil)
614 (when (functionp (third (assoc initarg e-def-initargs)))
615 (return t))))
616 (push slot (condition-classoid-hairy-slots classoid)))))))
617 (when *type-system-initialized*
618 (dolist (fun *define-condition-hooks*)
619 (funcall fun classoid))))))
620 name)
622 (defmacro define-condition (name (&rest parent-types) (&rest slot-specs)
623 &body options)
624 "DEFINE-CONDITION Name (Parent-Type*) (Slot-Spec*) Option*
625 Define NAME as a condition type. This new type inherits slots and its
626 report function from the specified PARENT-TYPEs. A slot spec is a list of:
627 (slot-name :reader <rname> :initarg <iname> {Option Value}*
629 The DEFINE-CLASS slot options :ALLOCATION, :INITFORM, [slot] :DOCUMENTATION
630 and :TYPE and the overall options :DEFAULT-INITARGS and
631 [type] :DOCUMENTATION are also allowed.
633 The :REPORT option is peculiar to DEFINE-CONDITION. Its argument is either
634 a string or a two-argument lambda or function name. If a function, the
635 function is called with the condition and stream to report the condition.
636 If a string, the string is printed.
638 Condition types are classes, but (as allowed by ANSI and not as described in
639 CLtL2) are neither STANDARD-OBJECTs nor STRUCTURE-OBJECTs. WITH-SLOTS and
640 SLOT-VALUE may not be used on condition objects."
641 (check-designator name 'define-condition)
642 (let* ((parent-types (or parent-types '(condition)))
643 (layout (find-condition-layout name parent-types))
644 (documentation nil)
645 (report nil)
646 (direct-default-initargs ()))
647 (collect ((slots)
648 (all-readers nil append)
649 (all-writers nil append))
650 (dolist (spec slot-specs)
651 (with-current-source-form (spec)
652 (when (keywordp spec)
653 (warn "Keyword slot name indicates probable syntax error:~% ~S"
654 spec))
655 (let* ((spec (if (consp spec) spec (list spec)))
656 (slot-name (first spec))
657 (allocation :instance)
658 (initform-p nil)
659 documentation
660 initform)
661 (collect ((initargs)
662 (readers)
663 (writers))
664 (do ((options (rest spec) (cddr options)))
665 ((null options))
666 (unless (and (consp options) (consp (cdr options)))
667 (error "malformed condition slot spec:~% ~S." spec))
668 (let ((arg (second options)))
669 (case (first options)
670 (:reader (readers arg))
671 (:writer (writers arg))
672 (:accessor
673 (readers arg)
674 (writers `(setf ,arg)))
675 (:initform
676 (when initform-p
677 (error "more than one :INITFORM in ~S" spec))
678 (setq initform-p t)
679 (setq initform arg))
680 (:initarg (initargs arg))
681 (:allocation
682 (setq allocation arg))
683 (:documentation
684 (when documentation
685 (error "more than one :DOCUMENTATION in ~S" spec))
686 (unless (stringp arg)
687 (error "slot :DOCUMENTATION argument is not a string: ~S"
688 arg))
689 (setq documentation arg))
690 (:type
691 (check-slot-type-specifier
692 arg slot-name (cons 'define-condition name)))
694 (error "unknown slot option:~% ~S" (first options))))))
696 (all-readers (readers))
697 (all-writers (writers))
698 (slots `(make-condition-slot
699 :name ',slot-name
700 :initargs ',(initargs)
701 :readers ',(readers)
702 :writers ',(writers)
703 :initform-p ',initform-p
704 :documentation ',documentation
705 :initform ,(when initform-p `',initform)
706 :initfunction ,(when initform-p
707 `#'(lambda () ,initform))
708 :allocation ',allocation))))))
710 (dolist (option options)
711 (unless (consp option)
712 (error "bad option:~% ~S" option))
713 (case (first option)
714 (:documentation (setq documentation (second option)))
715 (:report
716 (let ((arg (second option)))
717 (setq report
718 `#'(named-lambda (condition-report ,name) (condition stream)
719 (declare (type condition condition)
720 (type stream stream))
721 ,@(if (stringp arg)
722 `((declare (ignore condition))
723 (write-string ,arg stream))
724 `((funcall #',arg condition stream)))))))
725 (:default-initargs
726 (doplist (initarg initform) (rest option)
727 (push ``(,',initarg ,',initform ,#'(lambda () ,initform))
728 direct-default-initargs)))
730 (error "unknown option: ~S" (first option)))))
732 ;; Maybe kill docstring, but only under the cross-compiler.
733 #+(and (not sb-doc) sb-xc-host) (setq documentation nil)
734 `(progn
735 ,@(when *top-level-form-p*
736 ;; Avoid dumping uninitialized layouts, for sb-fasl::dump-layout
737 `((eval-when (:compile-toplevel)
738 (%compiler-define-condition ',name ',parent-types ,layout
739 ',(all-readers) ',(all-writers)))))
740 (%define-condition ',name
741 ',parent-types
742 ,(if *top-level-form-p*
743 layout
744 `(find-condition-layout ',name ',parent-types))
745 (list ,@(slots))
746 (list ,@direct-default-initargs)
747 ',(all-readers)
748 ',(all-writers)
749 (sb-c:source-location)
750 ,@(and documentation
751 `(,documentation)))
752 ;; This needs to be after %DEFINE-CONDITION in case :REPORT
753 ;; is a lambda referring to condition slot accessors:
754 ;; they're not proclaimed as functions before it has run if
755 ;; we're under EVAL or loaded as source.
756 (%set-condition-report ',name ,report)
757 ',name))))
759 ;;; Compute the effective slots of CLASS, copying inherited slots and
760 ;;; destructively modifying direct slots.
762 ;;; FIXME: It'd be nice to explain why it's OK to destructively modify
763 ;;; direct slots. Presumably it follows from the semantics of
764 ;;; inheritance and redefinition of conditions, but finding the cite
765 ;;; and documenting it here would be good. (Or, if this is not in fact
766 ;;; ANSI-compliant, fixing it would also be good.:-)
767 (defun compute-effective-slots (class)
768 (collect ((res (copy-list (condition-classoid-slots class))))
769 (dolist (sclass (cdr (condition-classoid-cpl class)))
770 (dolist (sslot (condition-classoid-slots sclass))
771 (let ((found (find (condition-slot-name sslot) (res)
772 :key #'condition-slot-name)))
773 (cond (found
774 (setf (condition-slot-initargs found)
775 (union (condition-slot-initargs found)
776 (condition-slot-initargs sslot)))
777 (unless (condition-slot-initform-p found)
778 (setf (condition-slot-initform-p found)
779 (condition-slot-initform-p sslot))
780 (setf (condition-slot-initform found)
781 (condition-slot-initform sslot))
782 (setf (condition-slot-initfunction found)
783 (condition-slot-initfunction sslot)))
784 (unless (condition-slot-allocation found)
785 (setf (condition-slot-allocation found)
786 (condition-slot-allocation sslot))))
788 (res (copy-structure sslot)))))))
789 (res)))
793 ;;;; various CONDITIONs specified by ANSI
795 (define-condition serious-condition (condition) ())
797 (define-condition error (serious-condition) ())
799 (define-condition warning (condition) ())
800 (define-condition style-warning (warning) ())
802 (defun simple-condition-printer (condition stream)
803 (let ((control (simple-condition-format-control condition)))
804 (if control
805 (apply #'format stream
806 control
807 (simple-condition-format-arguments condition))
808 (error "No format-control for ~S" condition))))
810 (define-condition simple-condition ()
811 ((format-control :reader simple-condition-format-control
812 :initarg :format-control
813 :initform nil
814 :type format-control)
815 (format-arguments :reader simple-condition-format-arguments
816 :initarg :format-arguments
817 :initform nil
818 :type list))
819 (:report simple-condition-printer))
821 (define-condition simple-warning (simple-condition warning) ())
823 (define-condition simple-error (simple-condition error) ())
825 (define-condition storage-condition (serious-condition) ())
827 (defun decode-type-error-context (context type)
828 (typecase context
829 (cons
830 (case (car context)
831 (struct-context
832 (format nil "when setting slot ~s of structure ~s"
833 (cddr context) (cadr context)))
834 (t context)))
835 ((eql sb-c::aref-context)
836 (let (*print-circle*)
837 (format nil "when setting an element of (ARRAY ~s)"
838 type)))
839 ((eql sb-c::ftype-context)
840 "from the function type declaration.")
841 ((and symbol
842 (not null))
843 (format nil "when binding ~s" context))
845 context)))
847 (define-condition type-error (error)
848 ((datum :reader type-error-datum :initarg :datum)
849 (expected-type :reader type-error-expected-type :initarg :expected-type)
850 (context :initform nil :reader type-error-context :initarg :context))
851 (:report report-general-type-error))
852 (defun report-general-type-error (condition stream)
853 (let ((type (type-error-expected-type condition))
854 (context (type-error-context condition)))
855 (if (eq context :multiple-values)
856 (format stream "~@<The values ~
857 ~@:_~2@T~S ~
858 ~@:_are not of type ~
859 ~@:_~2@T~/sb-impl:print-type-specifier/~:@>"
860 (type-error-datum condition)
861 type)
862 (format stream "~@<The value ~
863 ~@:_~2@T~S ~
864 ~@:_is not of type ~
865 ~@:_~2@T~/sb-impl:print-type-specifier/~@[ ~
866 ~@:_~a~]~:@>"
867 (type-error-datum condition)
868 type
869 (decode-type-error-context (type-error-context condition)
870 type)))))
872 ;;; not specified by ANSI, but too useful not to have around.
873 (define-condition simple-style-warning (simple-condition style-warning) ())
874 (define-condition simple-type-error (simple-condition type-error) ())
876 (define-condition program-error (error) ())
877 (define-condition parse-error (error) ())
878 (define-condition control-error (error) ())
879 (define-condition stream-error (error)
880 ((stream :reader stream-error-stream :initarg :stream)))
882 (define-condition end-of-file (stream-error) ()
883 (:report
884 (lambda (condition stream)
885 (format stream
886 "end of file on ~S"
887 (stream-error-stream condition)))))
889 (define-condition closed-stream-error (stream-error) ()
890 (:report
891 (lambda (condition stream)
892 (format stream "~S is closed" (stream-error-stream condition)))))
894 (define-condition closed-saved-stream-error (closed-stream-error) ()
895 (:report
896 (lambda (condition stream)
897 (format stream "~S was closed by SB-EXT:SAVE-LISP-AND-DIE" (stream-error-stream condition)))))
899 (define-condition file-error (error)
900 ((pathname :reader file-error-pathname :initarg :pathname))
901 (:report
902 (lambda (condition stream)
903 (format stream "error on file ~S" (file-error-pathname condition)))))
905 (define-condition package-error (error)
906 ((package :reader package-error-package :initarg :package)))
908 (define-condition cell-error (error)
909 ((name :reader cell-error-name :initarg :name)))
911 (define-condition values-list-argument-error (type-error)
913 (:report
914 (lambda (condition stream)
915 (format stream "~@<Attempt to use ~S on a dotted list or non-list: ~
916 ~2I~_~S~:>"
917 'values-list (type-error-datum condition)))))
919 (define-condition unbound-variable (cell-error)
920 ((not-yet-loaded :initform nil :reader not-yet-loaded :initarg :not-yet-loaded))
921 (:report
922 (lambda (condition stream)
923 (format stream
924 "~@<The variable ~S is unbound.~@?~@:>"
925 (cell-error-name condition)
926 (case (not-yet-loaded condition)
927 (:local
928 "~:@_It is a local variable ~
929 not available at compile-time.")
931 ""))))))
933 (define-condition undefined-function (cell-error)
934 ((not-yet-loaded :initform nil :reader not-yet-loaded :initarg :not-yet-loaded))
935 (:report
936 (lambda (condition stream)
937 (let ((name (cell-error-name condition)))
938 (format stream
939 (if (and (symbolp name) (macro-function name))
940 (sb-format:tokens "~@<~/sb-ext:print-symbol-with-prefix/ is a macro, ~
941 not a function.~@:>")
942 (sb-format:tokens "~@<The function ~/sb-ext:print-symbol-with-prefix/ ~
943 is undefined.~@?~@:>"))
944 name
945 (case (not-yet-loaded condition)
946 (:local
947 (sb-format:tokens "~:@_It is a local function ~
948 not available at compile-time."))
949 ((t) (sb-format:tokens "~:@_It is defined earlier in the ~
950 file but is not available at compile-time."))
952 "")))))))
954 (define-condition retry-undefined-function
955 (simple-condition undefined-function) ())
957 (define-condition special-form-function (undefined-function) ()
958 (:report
959 (lambda (condition stream)
960 (format stream
961 "Cannot FUNCALL the SYMBOL-FUNCTION of special operator ~S."
962 (cell-error-name condition)))))
964 (define-condition arithmetic-error (error)
965 ((operation :reader arithmetic-error-operation
966 :initarg :operation
967 :initform nil)
968 (operands :reader arithmetic-error-operands
969 :initarg :operands))
970 (:report (lambda (condition stream)
971 (format stream
972 "arithmetic error ~S signalled"
973 (type-of condition))
974 (when (arithmetic-error-operation condition)
975 (format stream
976 "~%Operation was (~S ~{~S~^ ~})."
977 (arithmetic-error-operation condition)
978 (arithmetic-error-operands condition))))))
980 (define-condition division-by-zero (arithmetic-error) ())
981 (define-condition floating-point-overflow (arithmetic-error) ())
982 (define-condition floating-point-underflow (arithmetic-error) ())
983 (define-condition floating-point-inexact (arithmetic-error) ())
984 (define-condition floating-point-invalid-operation (arithmetic-error) ())
986 (define-condition illegal-class-name-error (error)
987 ((name :initarg :name :reader illegal-class-name-error-name))
988 (:default-initargs :name (missing-arg))
989 (:report (lambda (condition stream)
990 (format stream "~@<~S is not a legal class name.~@:>"
991 (illegal-class-name-error-name condition)))))
993 (define-condition print-not-readable (error)
994 ((object :reader print-not-readable-object :initarg :object))
995 (:report
996 (lambda (condition stream)
997 (let ((obj (print-not-readable-object condition))
998 (*print-array* nil))
999 (format stream "~S cannot be printed readably." obj)))))
1001 (define-condition reader-error (parse-error stream-error) ()
1002 (:report (lambda (condition stream)
1003 (%report-reader-error condition stream))))
1005 ;;; a READER-ERROR whose REPORTing is controlled by FORMAT-CONTROL and
1006 ;;; FORMAT-ARGS (the usual case for READER-ERRORs signalled from
1007 ;;; within SBCL itself)
1009 ;;; (Inheriting CL:SIMPLE-CONDITION here isn't quite consistent with
1010 ;;; the letter of the ANSI spec: this is not a condition signalled by
1011 ;;; SIGNAL when a format-control is supplied by the function's first
1012 ;;; argument. It seems to me (WHN) to be basically in the spirit of
1013 ;;; the spec, but if not, it'd be straightforward to do our own
1014 ;;; DEFINE-CONDITION SB-INT:SIMPLISTIC-CONDITION with
1015 ;;; FORMAT-CONTROL and FORMAT-ARGS slots, and use that condition in
1016 ;;; place of CL:SIMPLE-CONDITION here.)
1017 (define-condition simple-reader-error (reader-error simple-condition)
1019 (:report (lambda (condition stream)
1020 (%report-reader-error condition stream :simple t))))
1022 ;;; base REPORTing of a READER-ERROR
1024 ;;; When SIMPLE, we expect and use SIMPLE-CONDITION-ish FORMAT-CONTROL
1025 ;;; and FORMAT-ARGS slots.
1026 (defun %report-reader-error (condition stream &key simple position)
1027 (let ((error-stream (stream-error-stream condition)))
1028 (pprint-logical-block (stream nil)
1029 (if simple
1030 (apply #'format stream
1031 (simple-condition-format-control condition)
1032 (simple-condition-format-arguments condition))
1033 (prin1 (class-name (class-of condition)) stream))
1034 (format stream "~2I~@[~:@_ ~:@_~:{~:(~A~): ~S~:^, ~:_~}~]~:@_ ~:@_Stream: ~S"
1035 (stream-error-position-info error-stream position)
1036 error-stream))))
1038 ;;;; special SBCL extension conditions
1040 ;;; an error apparently caused by a bug in SBCL itself
1042 ;;; Note that we don't make any serious effort to use this condition
1043 ;;; for *all* errors in SBCL itself. E.g. type errors and array
1044 ;;; indexing errors can occur in functions called from SBCL code, and
1045 ;;; will just end up as ordinary TYPE-ERROR or invalid index error,
1046 ;;; because the signalling code has no good way to know that the
1047 ;;; underlying problem is a bug in SBCL. But in the fairly common case
1048 ;;; that the signalling code does know that it's found a bug in SBCL,
1049 ;;; this condition is appropriate, reusing boilerplate and helping
1050 ;;; users to recognize it as an SBCL bug.
1051 (define-condition bug (simple-error)
1053 (:report
1054 (lambda (condition stream)
1055 (format stream
1056 "~@< ~? ~:@_~?~:>"
1057 (simple-condition-format-control condition)
1058 (simple-condition-format-arguments condition)
1059 "~@<This is probably a bug in SBCL itself. (Alternatively, ~
1060 SBCL might have been corrupted by bad user code, e.g. by an ~
1061 undefined Lisp operation like ~S, or by stray pointers from ~
1062 alien code or from unsafe Lisp code; or there might be a bug ~
1063 in the OS or hardware that SBCL is running on.) If it seems to ~
1064 be a bug in SBCL itself, the maintainers would like to know ~
1065 about it. Bug reports are welcome on the SBCL ~
1066 mailing lists, which you can find at ~
1067 <http://sbcl.sourceforge.net/>.~:@>"
1068 '((fmakunbound 'compile))))))
1070 (define-condition simple-storage-condition (storage-condition simple-condition)
1073 (define-condition sanitizer-error (simple-error)
1074 ((value :reader sanitizer-error-value :initarg :value)
1075 (address :reader sanitizer-error-address :initarg :address)
1076 (size :reader sanitizer-error-size :initarg :size)))
1078 ;;; a condition for use in stubs for operations which aren't supported
1079 ;;; on some platforms
1081 ;;; E.g. in sbcl-0.7.0.5, it might be appropriate to do something like
1082 ;;; #-(or freebsd linux)
1083 ;;; (defun load-foreign (&rest rest)
1084 ;;; (error 'unsupported-operator :name 'load-foreign))
1085 ;;; #+(or freebsd linux)
1086 ;;; (defun load-foreign ... actual definition ...)
1087 ;;; By signalling a standard condition in this case, we make it
1088 ;;; possible for test code to distinguish between (1) intentionally
1089 ;;; unimplemented and (2) unintentionally just screwed up somehow.
1090 ;;; (Before this condition was defined, test code tried to deal with
1091 ;;; this by checking for FBOUNDP, but that didn't work reliably. In
1092 ;;; sbcl-0.7.0, a package screwup left the definition of
1093 ;;; LOAD-FOREIGN in the wrong package, so it was unFBOUNDP even on
1094 ;;; architectures where it was supposed to be supported, and the
1095 ;;; regression tests cheerfully passed because they assumed that
1096 ;;; unFBOUNDPness meant they were running on an system which didn't
1097 ;;; support the extension.)
1098 (define-condition unsupported-operator (simple-error) ())
1100 ;;; (:ansi-cl :function remove)
1101 ;;; (:ansi-cl :section (a b c))
1102 ;;; (:ansi-cl :glossary "similar")
1104 ;;; (:sbcl :node "...")
1105 ;;; (:sbcl :variable *ed-functions*)
1108 ;;; FIXME: this is not the right place for this.
1109 (defun print-reference (reference stream)
1110 (ecase (car reference)
1111 (:amop
1112 (format stream "AMOP")
1113 (format stream ", ")
1114 (destructuring-bind (type data) (cdr reference)
1115 (ecase type
1116 (:readers "Readers for ~:(~A~) Metaobjects"
1117 (substitute #\ #\- (symbol-name data)))
1118 (:initialization
1119 (format stream "Initialization of ~:(~A~) Metaobjects"
1120 (substitute #\ #\- (symbol-name data))))
1121 (:generic-function (format stream "Generic Function ~S" data))
1122 (:function (format stream "Function ~S" data))
1123 (:section (format stream "Section ~{~D~^.~}" data)))))
1124 (:ansi-cl
1125 (format stream "The ANSI Standard")
1126 (format stream ", ")
1127 (destructuring-bind (type data) (cdr reference)
1128 (ecase type
1129 (:function (format stream "Function ~S" data))
1130 (:special-operator (format stream "Special Operator ~S" data))
1131 (:macro (format stream "Macro ~S" data))
1132 (:section (format stream "Section ~{~D~^.~}" data))
1133 (:glossary (format stream "Glossary entry for ~S" data))
1134 (:type (format stream "Type ~S" data))
1135 (:system-class (format stream "System Class ~S" data))
1136 (:issue (format stream "writeup for Issue ~A" data)))))
1137 (:sbcl
1138 (format stream "The SBCL Manual")
1139 (format stream ", ")
1140 (destructuring-bind (type data) (cdr reference)
1141 (ecase type
1142 (:node (format stream "Node ~S" data))
1143 (:variable (format stream "Variable ~S" data))
1144 (:function (format stream "Function ~S" data)))))
1145 ;; FIXME: other documents (e.g. CLIM, Franz documentation :-)
1147 (define-condition reference-condition ()
1148 ((references :initarg :references :reader reference-condition-references)))
1149 (defvar *print-condition-references* t)
1151 (define-condition simple-reference-error (reference-condition simple-error)
1154 (define-condition simple-reference-warning (reference-condition simple-warning)
1157 (define-condition arguments-out-of-domain-error
1158 (arithmetic-error reference-condition)
1161 ;; per CLHS: "The consequences are unspecified if functions are ...
1162 ;; multiply defined in the same file." so we are within reason to do any
1163 ;; unspecified behavior at compile-time and/or time, but the compiler was
1164 ;; annoyingly mum about genuinely inadvertent duplicate macro definitions.
1165 ;; Redefinition is henceforth a style-warning, and for compatibility it does
1166 ;; not cause the ERRORP value from COMPILE-TIME to be T.
1167 ;; Nor do we cite section 3.2.2.3 as the governing prohibition.
1168 (defun report-duplicate-definition (condition stream)
1169 (format stream "~@<Duplicate definition for ~S found in one file.~@:>"
1170 (slot-value condition 'name)))
1172 (define-condition duplicate-definition (reference-condition warning)
1173 ((name :initarg :name :reader duplicate-definition-name))
1174 (:report report-duplicate-definition)
1175 (:default-initargs :references '((:ansi-cl :section (3 2 2 3)))))
1176 ;; To my thinking, DUPLICATE-DEFINITION should be the ancestor condition,
1177 ;; and not fatal. But changing the meaning of that concept would be a bad idea,
1178 ;; so instead there is a new condition for the softer variant, which does not
1179 ;; inherit from the former.
1180 (define-condition same-file-redefinition-warning (style-warning)
1181 ;; Slot readers aren't proper generic functions until CLOS is built,
1182 ;; so this doesn't get a reader because you can't pick the same name,
1183 ;; and it wouldn't do any good to pick a different name that nothing knows.
1184 ((name :initarg :name))
1185 (:report report-duplicate-definition))
1187 (define-condition constant-modified (reference-condition warning)
1188 ((fun-name :initarg :fun-name :reader constant-modified-fun-name)
1189 (values :initform nil :initarg :values :reader constant-modified-values))
1190 (:report (lambda (c s)
1191 (format s "~@<Destructive function ~S called on ~
1192 constant data: ~{~s~^, ~}~:>"
1193 (constant-modified-fun-name c)
1194 (constant-modified-values c))))
1195 (:default-initargs :references '((:ansi-cl :special-operator quote)
1196 (:ansi-cl :section (3 7 1)))))
1198 (define-condition macro-arg-modified (constant-modified)
1199 ((variable :initform nil :initarg :variable :reader macro-arg-modified-variable))
1200 (:report (lambda (c s)
1201 (format s "~@<Destructive function ~S called on a macro argument: ~S.~:>"
1202 (constant-modified-fun-name c)
1203 (macro-arg-modified-variable c))))
1204 (:default-initargs :references nil))
1206 (define-condition package-at-variance (reference-condition simple-warning)
1208 (:default-initargs :references '((:ansi-cl :macro defpackage)
1209 (:sbcl :variable *on-package-variance*))))
1211 (define-condition package-at-variance-error (reference-condition simple-condition
1212 package-error)
1214 (:default-initargs :references '((:ansi-cl :macro defpackage))))
1216 (define-condition defconstant-uneql (reference-condition error)
1217 ((name :initarg :name :reader defconstant-uneql-name)
1218 (old-value :initarg :old-value :reader defconstant-uneql-old-value)
1219 (new-value :initarg :new-value :reader defconstant-uneql-new-value))
1220 (:report
1221 (lambda (condition stream)
1222 (format stream
1223 "~@<The constant ~S is being redefined (from ~S to ~S)~@:>"
1224 (defconstant-uneql-name condition)
1225 (defconstant-uneql-old-value condition)
1226 (defconstant-uneql-new-value condition))))
1227 (:default-initargs :references '((:ansi-cl :macro defconstant)
1228 (:sbcl :node "Idiosyncrasies"))))
1230 (define-condition array-initial-element-mismatch
1231 (reference-condition simple-warning)
1233 (:default-initargs
1234 :references '((:ansi-cl :function make-array)
1235 (:ansi-cl :function upgraded-array-element-type))))
1237 (define-condition initial-element-mismatch-style-warning
1238 (array-initial-element-mismatch simple-style-warning)
1241 (define-condition type-warning (reference-condition simple-warning)
1243 (:default-initargs :references '((:sbcl :node "Handling of Types"))))
1244 (define-condition type-style-warning (reference-condition simple-style-warning)
1246 (:default-initargs :references '((:sbcl :node "Handling of Types"))))
1247 (define-condition slot-initform-type-style-warning (type-style-warning) ())
1249 (define-condition local-argument-mismatch (reference-condition simple-warning)
1251 (:default-initargs :references '((:ansi-cl :section (3 2 2 3)))))
1253 (define-condition format-args-mismatch (reference-condition)
1255 (:default-initargs :references '((:ansi-cl :section (22 3 10 2)))))
1257 (define-condition format-too-few-args-warning
1258 (format-args-mismatch simple-warning)
1260 (define-condition format-too-many-args-warning
1261 (format-args-mismatch simple-style-warning)
1264 (define-condition implicit-generic-function-warning (style-warning)
1265 ((name :initarg :name :reader implicit-generic-function-name))
1266 (:report
1267 (lambda (condition stream)
1268 (format stream "~@<Implicitly creating new generic function ~
1269 ~/sb-ext:print-symbol-with-prefix/.~:@>"
1270 (implicit-generic-function-name condition)))))
1272 (define-condition extension-failure (reference-condition simple-error)
1275 (define-condition structure-initarg-not-keyword
1276 (reference-condition simple-style-warning)
1278 (:default-initargs :references '((:ansi-cl :section (2 4 8 13)))))
1280 (define-condition package-lock-violation (package-error
1281 reference-condition
1282 simple-condition)
1283 ((current-package :initform *package*
1284 :reader package-lock-violation-in-package))
1285 (:report
1286 (lambda (condition stream)
1287 (let ((control (simple-condition-format-control condition))
1288 (error-package (package-name
1289 (package-error-package condition)))
1290 (current-package (package-name
1291 (package-lock-violation-in-package condition))))
1292 (format stream "~@<Lock on package ~A violated~@[~{ when ~?~}~] ~
1293 while in package ~A.~:@>"
1294 error-package
1295 (when control
1296 (list control (simple-condition-format-arguments condition)))
1297 current-package))))
1298 ;; no :default-initargs -- reference-stuff provided by the
1299 ;; signalling form in target-package.lisp
1300 (:documentation
1301 "Subtype of CL:PACKAGE-ERROR. A subtype of this error is signalled
1302 when a package-lock is violated."))
1304 (define-condition package-locked-error (package-lock-violation) ()
1305 (:documentation
1306 "Subtype of SB-EXT:PACKAGE-LOCK-VIOLATION. An error of this type is
1307 signalled when an operation on a package violates a package lock."))
1309 (define-condition symbol-package-locked-error (package-lock-violation)
1310 ((symbol :initarg :symbol :reader package-locked-error-symbol))
1311 (:documentation
1312 "Subtype of SB-EXT:PACKAGE-LOCK-VIOLATION. An error of this type is
1313 signalled when an operation on a symbol violates a package lock. The
1314 symbol that caused the violation is accessed by the function
1315 SB-EXT:PACKAGE-LOCKED-ERROR-SYMBOL."))
1317 (define-condition undefined-alien-error (cell-error) ()
1318 (:report
1319 (lambda (condition stream)
1320 (if (slot-boundp condition 'name)
1321 (format stream "Undefined alien: ~S" (cell-error-name condition))
1322 (format stream "Undefined alien symbol.")))))
1324 (define-condition undefined-alien-variable-error (undefined-alien-error) ()
1325 (:report
1326 (lambda (condition stream)
1327 (declare (ignore condition))
1328 (format stream "Attempt to access an undefined alien variable."))))
1330 (define-condition undefined-alien-function-error (undefined-alien-error) ()
1331 (:report
1332 (lambda (condition stream)
1333 (if (and (slot-boundp condition 'name)
1334 (cell-error-name condition))
1335 (format stream "The alien function ~s is undefined."
1336 (cell-error-name condition))
1337 (format stream "Attempt to call an undefined alien function.")))))
1339 (define-condition unknown-keyword-argument (program-error)
1340 ((name :reader unknown-keyword-argument-name :initarg :name))
1341 (:report
1342 (lambda (condition stream)
1343 (format stream "Unknown &KEY argument: ~S"
1344 (unknown-keyword-argument-name condition)))))
1347 ;;;; various other (not specified by ANSI) CONDITIONs
1348 ;;;;
1349 ;;;; These might logically belong in other files; they're here, after
1350 ;;;; setup of CONDITION machinery, only because that makes it easier to
1351 ;;;; get cold init to work.
1353 ;;; OAOOM warning: see cross-condition.lisp
1354 (define-condition encapsulated-condition (condition)
1355 ((condition :initarg :condition :reader encapsulated-condition)))
1357 ;;; KLUDGE: a condition for floating point errors when we can't or
1358 ;;; won't figure out what type they are. (In FreeBSD and OpenBSD we
1359 ;;; don't know how, at least as of sbcl-0.6.7; in Linux we probably
1360 ;;; know how but the old code was broken by the conversion to POSIX
1361 ;;; signal handling and hasn't been fixed as of sbcl-0.6.7.)
1363 ;;; FIXME: Perhaps this should also be a base class for all
1364 ;;; floating point exceptions?
1365 (define-condition floating-point-exception (arithmetic-error)
1366 ((flags :initarg :traps
1367 :initform nil
1368 :reader floating-point-exception-traps))
1369 (:report (lambda (condition stream)
1370 (format stream
1371 "An arithmetic error ~S was signalled.~%"
1372 (type-of condition))
1373 (let ((traps (floating-point-exception-traps condition)))
1374 (if traps
1375 (format stream
1376 "Trapping conditions are: ~%~{ ~S~^~}~%"
1377 traps)
1378 (write-line
1379 "No traps are enabled? How can this be?"
1380 stream))))))
1382 (define-condition invalid-array-index-error (type-error)
1383 ((array :initarg :array :reader invalid-array-index-error-array)
1384 (axis :initarg :axis :reader invalid-array-index-error-axis))
1385 (:report
1386 (lambda (condition stream)
1387 (let ((array (invalid-array-index-error-array condition))
1388 (index (type-error-datum condition)))
1389 (if (integerp index)
1390 (format stream "Invalid index ~S for ~@[axis ~W of ~]~S, ~
1391 should be a non-negative integer below ~W."
1392 (type-error-datum condition)
1393 (when (> (array-rank array) 1)
1394 (invalid-array-index-error-axis condition))
1395 (type-of array)
1396 ;; Extract the bound from (INTEGER 0 (BOUND))
1397 (caaddr (type-error-expected-type condition)))
1398 (format stream "~s is not of type INTEGER." index))))))
1400 (define-condition invalid-array-error (reference-condition type-error) ()
1401 (:report
1402 (lambda (condition stream)
1403 (let ((*print-array* nil))
1404 (format stream
1405 "~@<Displaced array originally of type ~
1406 ~/sb-impl:print-type-specifier/ has been invalidated ~
1407 due its displaced-to array ~S having become too small ~
1408 to hold it: the displaced array's dimensions have all ~
1409 been set to zero to trap accesses to it.~:@>"
1410 (type-error-expected-type condition)
1411 (array-displacement (type-error-datum condition))))))
1412 (:default-initargs
1413 :references
1414 (list '(:ansi-cl :function adjust-array))))
1416 (define-condition uninitialized-element-error (cell-error) ()
1417 (:report
1418 (lambda (condition stream)
1419 ;; NAME is a cons of the array and index
1420 (destructuring-bind (array . index) (cell-error-name condition)
1421 (declare (ignorable index))
1422 #+ubsan
1423 (let* ((origin-pc
1424 (ash (sb-vm::vector-extra-data
1425 (if (simple-vector-p array)
1426 array
1427 (sb-vm::vector-extra-data array)))
1428 -3)) ; XXX: ubsan magic
1429 (origin-code (sb-di::code-header-from-pc (int-sap origin-pc))))
1430 (let ((*print-array* nil))
1431 (format stream "Element ~D of array ~_~S ~_was not assigned a value.~%Origin=~X"
1432 index array (or origin-code origin-pc))))
1433 #-ubsan
1434 ;; FOLD-INDEX-ADDRESSING could render INDEX wrong. There's no way to know.
1435 (let ((*print-array* nil))
1436 (format stream "Uninitialized element accessed in array ~S"
1437 array))))))
1440 ;;; We signal this one for SEQUENCE operations, but INVALID-ARRAY-INDEX-ERROR
1441 ;;; for arrays. Might it be better to use the above condition for operations
1442 ;;; on SEQUENCEs that happen to be arrays?
1443 (define-condition index-too-large-error (type-error)
1444 ((sequence :initarg :sequence))
1445 (:report
1446 (lambda (condition stream)
1447 (let ((sequence (slot-value condition 'sequence))
1448 (index (type-error-datum condition)))
1449 (if (vectorp sequence)
1450 (format stream "Invalid index ~W for ~S ~@[with fill-pointer ~a~], ~
1451 should be a non-negative integer below ~W."
1452 index
1453 (type-of sequence)
1454 (and (array-has-fill-pointer-p sequence)
1455 (fill-pointer sequence))
1456 (length sequence))
1457 (format stream
1458 "The index ~S is too large for a ~a of length ~s."
1459 index
1460 (if (listp sequence)
1461 "list"
1462 "sequence")
1463 (length sequence)))))))
1465 (define-condition bounding-indices-bad-error (reference-condition type-error)
1466 ((object :reader bounding-indices-bad-object :initarg :object))
1467 (:report
1468 (lambda (condition stream)
1469 (let* ((datum (type-error-datum condition))
1470 (start (car datum))
1471 (end (cdr datum))
1472 (object (bounding-indices-bad-object condition)))
1473 (etypecase object
1474 (sequence
1475 (format stream
1476 "The bounding indices ~S and ~S are bad ~
1477 for a sequence of length ~S."
1478 start end (length object)))
1479 (array
1480 ;; from WITH-ARRAY-DATA
1481 (format stream
1482 "The START and END parameters ~S and ~S are ~
1483 bad for an array of total size ~S."
1484 start end (array-total-size object)))))))
1485 (:default-initargs
1486 :references
1487 (list '(:ansi-cl :glossary "bounding index designator")
1488 '(:ansi-cl :issue "SUBSEQ-OUT-OF-BOUNDS:IS-AN-ERROR"))))
1490 (define-condition nil-array-accessed-error (reference-condition type-error)
1492 (:report (lambda (condition stream)
1493 (declare (ignore condition))
1494 (format stream
1495 "An attempt to access an array of element-type ~
1496 NIL was made. Congratulations!")))
1497 (:default-initargs
1498 :references '((:ansi-cl :function upgraded-array-element-type)
1499 (:ansi-cl :section (15 1 2 1))
1500 (:ansi-cl :section (15 1 2 2)))))
1502 (define-condition namestring-parse-error (parse-error)
1503 ((complaint :reader namestring-parse-error-complaint :initarg :complaint)
1504 (args :reader namestring-parse-error-args :initarg :args :initform nil)
1505 (namestring :reader namestring-parse-error-namestring :initarg :namestring)
1506 (offset :reader namestring-parse-error-offset :initarg :offset))
1507 (:report
1508 (lambda (condition stream)
1509 (format stream
1510 "parse error in namestring: ~?~% ~A~% ~V@T^"
1511 (namestring-parse-error-complaint condition)
1512 (namestring-parse-error-args condition)
1513 (namestring-parse-error-namestring condition)
1514 (namestring-parse-error-offset condition)))))
1516 (define-condition pathname-unparse-error (file-error
1517 simple-condition)
1518 ((problem :reader pathname-unparse-error-problem :initarg :problem))
1519 (:report (lambda (condition stream)
1520 (format stream "~@<The pathname ~S ~A~:[.~; because ~:*~?~]~@:>"
1521 (file-error-pathname condition)
1522 (pathname-unparse-error-problem condition)
1523 (simple-condition-format-control condition)
1524 (simple-condition-format-arguments condition))))
1525 (:default-initargs
1526 :problem (missing-arg)))
1528 (define-condition no-namestring-error (pathname-unparse-error
1529 reference-condition)
1531 (:default-initargs
1532 :problem "does not have a namestring"
1533 :references '((:ansi-cl :section (19 1 2)))))
1534 (defun no-namestring-error
1535 (pathname &optional format-control &rest format-arguments)
1536 (error 'no-namestring-error
1537 :pathname pathname
1538 :format-control format-control :format-arguments format-arguments))
1540 (define-condition no-native-namestring-error (pathname-unparse-error)
1542 (:default-initargs
1543 :problem "does not have a native namestring"))
1544 (defun no-native-namestring-error
1545 (pathname &optional format-control &rest format-arguments)
1546 (error 'no-native-namestring-error
1547 :pathname pathname
1548 :format-control format-control :format-arguments format-arguments))
1550 (define-condition simple-package-error (simple-condition package-error) ())
1552 (define-condition package-does-not-exist (simple-package-error) ())
1554 (define-condition simple-reader-package-error (simple-reader-error package-error) ())
1555 (define-condition reader-package-does-not-exist (simple-reader-package-error package-does-not-exist) ())
1557 (define-condition reader-eof-error (end-of-file)
1558 ((context :reader reader-eof-error-context :initarg :context))
1559 (:report
1560 (lambda (condition stream)
1561 (format stream
1562 "unexpected end of file on ~S ~A"
1563 (stream-error-stream condition)
1564 (reader-eof-error-context condition)))))
1566 (define-condition reader-impossible-number-error (simple-reader-error)
1567 ((error :reader reader-impossible-number-error-error :initarg :error))
1568 (:report
1569 (lambda (condition stream)
1570 (let ((error-stream (stream-error-stream condition)))
1571 (format stream
1572 "READER-ERROR ~@[at ~W ~]on ~S:~%~?~%Original error: ~A"
1573 (sb-impl::file-position-or-nil-for-error error-stream) error-stream
1574 (simple-condition-format-control condition)
1575 (simple-condition-format-arguments condition)
1576 (reader-impossible-number-error-error condition))))))
1578 (define-condition standard-readtable-modified-error (reference-condition error)
1579 ((operation :initarg :operation :reader standard-readtable-modified-operation))
1580 (:report (lambda (condition stream)
1581 (format stream "~S would modify the standard readtable."
1582 (standard-readtable-modified-operation condition))))
1583 (:default-initargs :references `((:ansi-cl :section (2 1 1 2))
1584 (:ansi-cl :glossary "standard readtable"))))
1586 (define-condition standard-pprint-dispatch-table-modified-error
1587 (reference-condition error)
1588 ((operation :initarg :operation
1589 :reader standard-pprint-dispatch-table-modified-operation))
1590 (:report (lambda (condition stream)
1591 (format stream "~S would modify the standard pprint dispatch table."
1592 (standard-pprint-dispatch-table-modified-operation
1593 condition))))
1594 (:default-initargs
1595 :references `((:ansi-cl :glossary "standard pprint dispatch table"))))
1597 (define-condition timeout (serious-condition)
1598 ((seconds :initarg :seconds :initform nil :reader timeout-seconds))
1599 (:report (lambda (condition stream)
1600 (format stream "Timeout occurred~@[ after ~A second~:P~]."
1601 (timeout-seconds condition))))
1602 (:documentation
1603 "Signaled when an operation does not complete within an allotted time budget."))
1605 (define-condition io-timeout (stream-error timeout)
1606 ((direction :reader io-timeout-direction :initarg :direction))
1607 (:report
1608 (lambda (condition stream)
1609 (declare (type stream stream))
1610 (format stream
1611 "I/O timeout while doing ~(~A~) on ~S."
1612 (io-timeout-direction condition)
1613 (stream-error-stream condition)))))
1615 (define-condition deadline-timeout (timeout)
1617 (:report (lambda (condition stream)
1618 (format stream "A deadline was reached after ~A second~:P."
1619 (timeout-seconds condition))))
1620 (:documentation
1621 "Signaled when an operation in the context of a deadline takes
1622 longer than permitted by the deadline."))
1624 (define-condition declaration-type-conflict-error (reference-condition
1625 simple-error)
1627 (:default-initargs
1628 :format-control
1629 #.(macroexpand-1 ; stuff in a literal #<fmt-control>
1630 '(sb-format:tokens "Symbol ~/sb-ext:print-symbol-with-prefix/ cannot ~
1631 be both the name of a type and the name of a declaration"))
1632 :references '((:ansi-cl :section (3 8 21)))))
1634 ;;; Single stepping conditions
1636 (define-condition step-condition ()
1637 ((form :initarg :form :reader step-condition-form))
1638 (:documentation "Common base class of single-stepping conditions.
1639 STEP-CONDITION-FORM holds a string representation of the form being
1640 stepped."))
1642 (setf (documentation 'step-condition-form 'function)
1643 "Form associated with the STEP-CONDITION.")
1645 (define-condition step-form-condition (step-condition)
1646 ((args :initarg :args :reader step-condition-args))
1647 (:report
1648 (lambda (condition stream)
1649 (let ((*print-circle* t)
1650 (*print-pretty* t)
1651 (*print-readably* nil))
1652 (format stream
1653 "Evaluating call:~%~< ~@;~A~:>~%~
1654 ~:[With arguments:~%~{ ~S~%~}~;With unknown arguments~]~%"
1655 (list (step-condition-form condition))
1656 (eq (step-condition-args condition) :unknown)
1657 (step-condition-args condition)))))
1658 (:documentation "Condition signalled by code compiled with
1659 single-stepping information when about to execute a form.
1660 STEP-CONDITION-FORM holds the form, STEP-CONDITION-PATHNAME holds the
1661 pathname of the original file or NIL, and STEP-CONDITION-SOURCE-PATH
1662 holds the source-path to the original form within that file or NIL.
1663 Associated with this condition are always the restarts STEP-INTO,
1664 STEP-NEXT, and STEP-CONTINUE."))
1666 (define-condition step-result-condition (step-condition)
1667 ((result :initarg :result :reader step-condition-result)))
1669 (setf (documentation 'step-condition-result 'function)
1670 "Return values associated with STEP-VALUES-CONDITION as a list,
1671 or the variable value associated with STEP-VARIABLE-CONDITION.")
1673 (define-condition step-values-condition (step-result-condition)
1675 (:documentation "Condition signalled by code compiled with
1676 single-stepping information after executing a form.
1677 STEP-CONDITION-FORM holds the form, and STEP-CONDITION-RESULT holds
1678 the values returned by the form as a list. No associated restarts."))
1680 (define-condition step-finished-condition (step-condition)
1682 (:report
1683 (lambda (condition stream)
1684 (declare (ignore condition))
1685 (format stream "Returning from STEP")))
1686 (:documentation "Condition signaled when STEP returns."))
1688 ;;; A knob for muffling warnings, mostly for use while loading files.
1689 (defvar *muffled-warnings* 'uninteresting-redefinition
1690 "A type that ought to specify a subtype of WARNING. Whenever a
1691 warning is signaled, if the warning is of this type and is not
1692 handled by any other handler, it will be muffled.")
1694 ;;; Various STYLE-WARNING signaled in the system.
1695 ;; For the moment, we're only getting into the details for function
1696 ;; redefinitions, but other redefinitions could be done later
1697 ;; (e.g. methods).
1698 (define-condition redefinition-warning (style-warning)
1699 ((name
1700 :initarg :name
1701 :reader redefinition-warning-name)
1702 (new-location
1703 :initarg :new-location
1704 :reader redefinition-warning-new-location)))
1706 (define-condition function-redefinition-warning (redefinition-warning)
1707 ((new-function
1708 :initarg :new-function
1709 :reader function-redefinition-warning-new-function)))
1711 (define-condition redefinition-with-defun (function-redefinition-warning)
1713 (:report (lambda (warning stream)
1714 (format stream "redefining ~/sb-ext:print-symbol-with-prefix/ ~
1715 in DEFUN"
1716 (redefinition-warning-name warning)))))
1718 (define-condition redefinition-with-defmacro (function-redefinition-warning)
1720 (:report (lambda (warning stream)
1721 (format stream "redefining ~/sb-ext:print-symbol-with-prefix/ ~
1722 in DEFMACRO"
1723 (redefinition-warning-name warning)))))
1725 (define-condition redefinition-with-defgeneric (redefinition-warning)
1727 (:report (lambda (warning stream)
1728 (format stream "redefining ~/sb-ext:print-symbol-with-prefix/ ~
1729 in DEFGENERIC"
1730 (redefinition-warning-name warning)))))
1732 (define-condition redefinition-with-defmethod (redefinition-warning)
1733 ((qualifiers :initarg :qualifiers
1734 :reader redefinition-with-defmethod-qualifiers)
1735 (specializers :initarg :specializers
1736 :reader redefinition-with-defmethod-specializers)
1737 (new-location :initarg :new-location
1738 :reader redefinition-with-defmethod-new-location)
1739 (old-method :initarg :old-method
1740 :reader redefinition-with-defmethod-old-method))
1741 (:report (lambda (warning stream)
1742 (format stream "redefining ~S~{ ~S~} ~S in DEFMETHOD"
1743 (redefinition-warning-name warning)
1744 (redefinition-with-defmethod-qualifiers warning)
1745 (redefinition-with-defmethod-specializers warning)))))
1747 ;;;; Deciding which redefinitions are "interesting".
1749 (defun function-file-namestring (function)
1750 (when (typep function 'interpreted-function)
1751 (return-from function-file-namestring
1752 #+sb-eval
1753 (sb-c:definition-source-location-namestring
1754 (sb-eval:interpreted-function-source-location function))
1755 #+sb-fasteval
1756 (awhen (sb-interpreter:fun-source-location function)
1757 (sb-c:definition-source-location-namestring it))))
1758 (let* ((fun (%fun-fun function))
1759 (code (fun-code-header fun))
1760 (debug-info (%code-debug-info code))
1761 (debug-source (when debug-info
1762 (sb-c::debug-info-source debug-info)))
1763 (namestring (when debug-source
1764 (debug-source-namestring debug-source))))
1765 namestring))
1767 (defun interesting-function-redefinition-warning-p (warning old)
1768 (let ((new (function-redefinition-warning-new-function warning)))
1770 ;; compiled->interpreted is interesting.
1771 (and (typep old 'compiled-function)
1772 (typep new '(not compiled-function)))
1773 ;; fin->regular is interesting except for interpreted->compiled.
1774 (and (typep new '(not funcallable-instance))
1775 (typep old '(and funcallable-instance (not interpreted-function))))
1776 ;; different file or unknown location is interesting.
1777 (let* ((old-namestring (function-file-namestring old))
1778 (new-namestring (function-file-namestring new)))
1779 (and (or (not old-namestring)
1780 (not new-namestring)
1781 (not (string= old-namestring new-namestring))))))))
1783 (setf (info :function :predicate-truth-constraint
1784 'uninteresting-ordinary-function-redefinition-p) 'warning)
1785 (defun uninteresting-ordinary-function-redefinition-p (warning)
1786 (and
1787 (typep warning 'redefinition-with-defun)
1788 ;; Shared logic.
1789 (let ((name (redefinition-warning-name warning)))
1790 (not (interesting-function-redefinition-warning-p
1791 warning (or (fdefinition name) (macro-function name)))))))
1793 (setf (info :function :predicate-truth-constraint
1794 'uninteresting-macro-redefinition-p) 'warning)
1795 (defun uninteresting-macro-redefinition-p (warning)
1796 (and
1797 (typep warning 'redefinition-with-defmacro)
1798 ;; Shared logic.
1799 (let ((name (redefinition-warning-name warning)))
1800 (not (interesting-function-redefinition-warning-p
1801 warning (or (macro-function name) (fdefinition name)))))))
1803 (setf (info :function :predicate-truth-constraint
1804 'uninteresting-generic-function-redefinition-p) 'warning)
1805 (defun uninteresting-generic-function-redefinition-p (warning)
1806 (and
1807 (typep warning 'redefinition-with-defgeneric)
1808 ;; Can't use the shared logic above, since GF's don't get a "new"
1809 ;; definition -- rather the FIN-FUNCTION is set.
1810 (let* ((name (redefinition-warning-name warning))
1811 (old (fdefinition name))
1812 (old-location (when (typep old 'generic-function)
1813 (sb-pcl::definition-source old)))
1814 (old-namestring (when old-location
1815 (sb-c:definition-source-location-namestring old-location)))
1816 (new-location (redefinition-warning-new-location warning))
1817 (new-namestring (when new-location
1818 (sb-c:definition-source-location-namestring new-location))))
1819 (and old-namestring
1820 new-namestring
1821 (string= old-namestring new-namestring)))))
1823 (setf (info :function :predicate-truth-constraint
1824 'uninteresting-method-redefinition-p) 'warning)
1825 (defun uninteresting-method-redefinition-p (warning)
1826 (and
1827 (typep warning 'redefinition-with-defmethod)
1828 ;; Can't use the shared logic above, since GF's don't get a "new"
1829 ;; definition -- rather the FIN-FUNCTION is set.
1830 (let* ((old-method (redefinition-with-defmethod-old-method warning))
1831 (old-location (sb-pcl::definition-source old-method))
1832 (old-namestring (when old-location
1833 (sb-c:definition-source-location-namestring old-location)))
1834 (new-location (redefinition-warning-new-location warning))
1835 (new-namestring (when new-location
1836 (sb-c:definition-source-location-namestring new-location))))
1837 (and new-namestring
1838 old-namestring
1839 (string= new-namestring old-namestring)))))
1841 (deftype uninteresting-redefinition ()
1842 '(or (satisfies uninteresting-ordinary-function-redefinition-p)
1843 (satisfies uninteresting-macro-redefinition-p)
1844 (satisfies uninteresting-generic-function-redefinition-p)
1845 (satisfies uninteresting-method-redefinition-p)))
1847 (define-condition redefinition-with-deftransform (redefinition-warning)
1848 ((transform :initarg :transform
1849 :reader redefinition-with-deftransform-transform))
1850 (:report (lambda (warning stream)
1851 (format stream "Overwriting ~S"
1852 (redefinition-with-deftransform-transform warning)))))
1854 ;;; Various other STYLE-WARNINGS
1855 (define-condition dubious-asterisks-around-variable-name
1856 (style-warning simple-condition)
1858 (:report (lambda (warning stream)
1859 (format stream "~@?, even though the name follows~@
1860 the usual naming convention (names like *FOO*) for special variables"
1861 (simple-condition-format-control warning)
1862 (simple-condition-format-arguments warning)))))
1864 (define-condition asterisks-around-lexical-variable-name
1865 (dubious-asterisks-around-variable-name)
1868 (define-condition asterisks-around-constant-variable-name
1869 (dubious-asterisks-around-variable-name)
1872 (define-condition &optional-and-&key-in-lambda-list (simple-style-warning) ())
1874 ;; We call this UNDEFINED-ALIEN-STYLE-WARNING because there are some
1875 ;; subclasses of ERROR above having to do with undefined aliens.
1876 (define-condition undefined-alien-style-warning (style-warning)
1877 ((symbol :initarg :symbol :reader undefined-alien-symbol))
1878 (:report (lambda (warning stream)
1879 (format stream "Undefined alien: ~S"
1880 (undefined-alien-symbol warning)))))
1882 ;;; Formerly this was guarded by "#+(or sb-eval sb-fasteval)", but
1883 ;;; why would someone build with no interpreter? And if they did,
1884 ;;; would they really care that one extra condition definition exists?
1885 (define-condition lexical-environment-too-complex (style-warning)
1886 ((form :initarg :form :reader lexical-environment-too-complex-form)
1887 (lexenv :initarg :lexenv :reader lexical-environment-too-complex-lexenv))
1888 (:report (lambda (warning stream)
1889 (format stream
1890 "~@<Native lexical environment too complex for ~
1891 SB-EVAL to evaluate ~S, falling back to ~
1892 SIMPLE-EVAL-IN-LEXENV. Lexenv: ~S~:@>"
1893 (lexical-environment-too-complex-form warning)
1894 (lexical-environment-too-complex-lexenv warning)))))
1896 ;; If the interpreter is in use (and the REPL is interpreted),
1897 ;; it's easy to accidentally make the macroexpand-hook an interpreted
1898 ;; function. So MACROEXPAND-1 is a little more careful,
1899 ;; and might signal this, instead of only EVAL being able to signal it.
1900 (define-condition macroexpand-hook-type-error (type-error)
1902 (:report (lambda (condition stream)
1903 (format stream "The value of *MACROEXPAND-HOOK* is not a designator for a compiled function: ~S"
1904 (type-error-datum condition)))))
1906 ;; Although this has -ERROR- in the name, it's just a STYLE-WARNING.
1907 (define-condition character-decoding-error-in-comment (style-warning)
1908 ((stream :initarg :stream :reader decoding-error-in-comment-stream)
1909 (position :initarg :position :reader decoding-error-in-comment-position))
1910 (:report (lambda (warning stream)
1911 (format stream
1912 "Character decoding error in a ~A-comment at ~
1913 position ~A reading source stream ~A, ~
1914 resyncing."
1915 (decoding-error-in-comment-macro warning)
1916 (decoding-error-in-comment-position warning)
1917 (decoding-error-in-comment-stream warning)))))
1919 (define-condition character-decoding-error-in-macro-char-comment
1920 (character-decoding-error-in-comment)
1921 ((char :initform #\; :initarg :char
1922 :reader character-decoding-error-in-macro-char-comment-char)))
1924 (define-condition character-decoding-error-in-dispatch-macro-char-comment
1925 (character-decoding-error-in-comment)
1926 ;; ANSI doesn't give a way for a reader function invoked by a
1927 ;; dispatch macro character to determine which dispatch character
1928 ;; was used, so if a user wants to signal one of these from a custom
1929 ;; comment reader, he'll have to supply the :DISP-CHAR himself.
1930 ((disp-char :initform #\# :initarg :disp-char
1931 :reader character-decoding-error-in-macro-char-comment-disp-char)
1932 (sub-char :initarg :sub-char
1933 :reader character-decoding-error-in-macro-char-comment-sub-char)))
1935 (defun decoding-error-in-comment-macro (warning)
1936 (etypecase warning
1937 (character-decoding-error-in-macro-char-comment
1938 (character-decoding-error-in-macro-char-comment-char warning))
1939 (character-decoding-error-in-dispatch-macro-char-comment
1940 (format
1941 nil "~C~C"
1942 (character-decoding-error-in-macro-char-comment-disp-char warning)
1943 (character-decoding-error-in-macro-char-comment-sub-char warning)))))
1945 (define-condition deprecated-eval-when-situations (style-warning)
1946 ((situations :initarg :situations
1947 :reader deprecated-eval-when-situations-situations))
1948 (:report (lambda (warning stream)
1949 (format stream "using deprecated EVAL-WHEN situation names~{ ~S~}"
1950 (deprecated-eval-when-situations-situations warning)))))
1952 (define-condition proclamation-mismatch (condition)
1953 ((kind :initarg :kind :reader proclamation-mismatch-kind)
1954 (description :initarg :description :reader proclamation-mismatch-description :initform nil)
1955 (name :initarg :name :reader proclamation-mismatch-name)
1956 (old :initarg :old :reader proclamation-mismatch-old)
1957 (new :initarg :new :reader proclamation-mismatch-new)
1958 (value :initarg :value))
1959 (:report
1960 (lambda (condition stream)
1961 (if (slot-boundp condition 'value)
1962 (format stream
1963 "~@<The new ~A proclamation for~@[ ~A~] ~
1964 ~/sb-ext:print-symbol-with-prefix/~
1965 ~@:_~2@T~/sb-impl:print-type-specifier/~@:_~
1966 does not match the current value ~S of type~
1967 ~@:_~2@T~/sb-impl:print-type-specifier/~@:>"
1968 (proclamation-mismatch-kind condition)
1969 (proclamation-mismatch-description condition)
1970 (proclamation-mismatch-name condition)
1971 (proclamation-mismatch-new condition)
1972 (slot-value condition 'value)
1973 (proclamation-mismatch-old condition))
1974 (format stream
1975 "~@<The new ~A proclamation for~@[ ~A~] ~
1976 ~/sb-ext:print-symbol-with-prefix/~
1977 ~@:_~2@T~/sb-impl:print-type-specifier/~@:_~
1978 does not match the old ~4:*~A~3* proclamation~
1979 ~@:_~2@T~/sb-impl:print-type-specifier/~@:>"
1980 (proclamation-mismatch-kind condition)
1981 (proclamation-mismatch-description condition)
1982 (proclamation-mismatch-name condition)
1983 (proclamation-mismatch-new condition)
1984 (proclamation-mismatch-old condition))))))
1986 (define-condition type-proclamation-mismatch (proclamation-mismatch)
1988 (:default-initargs :kind 'type))
1990 (define-condition type-proclamation-mismatch-warning (style-warning
1991 type-proclamation-mismatch)
1994 (define-condition ftype-proclamation-mismatch (proclamation-mismatch)
1996 (:default-initargs :kind 'ftype))
1998 (define-condition ftype-proclamation-mismatch-warning (style-warning
1999 ftype-proclamation-mismatch)
2002 (define-condition ftype-proclamation-mismatch-error (error
2003 ftype-proclamation-mismatch)
2005 (:default-initargs :kind 'ftype :description "known function"))
2007 (define-condition ftype-proclamation-derived-mismatch-warning (ftype-proclamation-mismatch-warning)
2009 (:report
2010 (lambda (condition stream)
2011 (format stream
2012 "~@<The new ~A proclamation for~@[ ~A~] ~
2013 ~/sb-ext:print-symbol-with-prefix/~
2014 ~@:_~2@T~/sb-impl:print-type-specifier/~@:_~
2015 does not match the derived return type~
2016 ~@:_~2@T~/sb-impl:print-type-specifier/~@:>"
2017 (proclamation-mismatch-kind condition)
2018 (proclamation-mismatch-description condition)
2019 (proclamation-mismatch-name condition)
2020 (proclamation-mismatch-new condition)
2021 (proclamation-mismatch-old condition)))))
2023 ;;;; deprecation conditions
2025 (define-condition deprecation-condition (reference-condition)
2026 ((namespace :initarg :namespace
2027 :reader deprecation-condition-namespace)
2028 (name :initarg :name
2029 :reader deprecation-condition-name)
2030 (replacements :initarg :replacements
2031 :reader deprecation-condition-replacements)
2032 (software :initarg :software
2033 :reader deprecation-condition-software)
2034 (version :initarg :version
2035 :reader deprecation-condition-version)
2036 (runtime-error :initarg :runtime-error
2037 :reader deprecation-condition-runtime-error
2038 :initform nil))
2039 (:default-initargs
2040 :namespace (missing-arg)
2041 :name (missing-arg)
2042 :replacements (missing-arg)
2043 :software (missing-arg)
2044 :version (missing-arg)
2045 :references '((:sbcl :node "Deprecation Conditions")))
2046 (:documentation
2047 "Superclass for deprecation-related error and warning
2048 conditions."))
2050 (defmethod print-object ((condition deprecation-condition) stream)
2051 (flet ((print-it (stream)
2052 (print-deprecation-message
2053 (deprecation-condition-namespace condition)
2054 (deprecation-condition-name condition)
2055 (deprecation-condition-software condition)
2056 (deprecation-condition-version condition)
2057 (deprecation-condition-replacements condition)
2058 stream)))
2059 (if *print-escape*
2060 (print-unreadable-object (condition stream :type t)
2061 (print-it stream))
2062 (print-it stream))))
2064 (macrolet ((define-deprecation-warning
2065 (name superclass check-runtime-error format-string
2066 &optional documentation)
2067 `(progn
2068 (define-condition ,name (,superclass deprecation-condition)
2070 ,@(when documentation
2071 `((:documentation ,documentation))))
2073 (defmethod print-object :after ((condition ,name) stream)
2074 (when (and (not *print-escape*)
2075 ,@(when check-runtime-error
2076 `((deprecation-condition-runtime-error condition))))
2077 (format stream ,format-string
2078 (deprecation-condition-software condition)
2079 (deprecation-condition-name condition)))))))
2081 ;; These conditions must not occur in self-build!
2082 (define-deprecation-warning early-deprecation-warning style-warning nil
2083 "~%~@<~:@_In future~@[ ~A~] versions ~
2084 ~/sb-ext:print-symbol-with-prefix/ will signal a full warning ~
2085 at compile-time.~:@>"
2086 "This warning is signaled when the use of a variable,
2087 function, type, etc. in :EARLY deprecation is detected at
2088 compile-time. The use will work at run-time with no warning or
2089 error.")
2091 (define-deprecation-warning late-deprecation-warning warning t
2092 "~%~@<~:@_In future~@[ ~A~] versions ~
2093 ~/sb-ext:print-symbol-with-prefix/ will signal a runtime ~
2094 error.~:@>"
2095 "This warning is signaled when the use of a variable,
2096 function, type, etc. in :LATE deprecation is detected at
2097 compile-time. The use will work at run-time with no warning or
2098 error.")
2100 (define-deprecation-warning final-deprecation-warning warning t
2101 "~%~@<~:@_~*An error will be signaled at runtime for ~
2102 ~/sb-ext:print-symbol-with-prefix/.~:@>"
2103 "This warning is signaled when the use of a variable,
2104 function, type, etc. in :FINAL deprecation is detected at
2105 compile-time. An error will be signaled at run-time."))
2107 (define-condition deprecation-error (error deprecation-condition)
2109 (:documentation
2110 "This error is signaled at run-time when an attempt is made to use
2111 a thing that is in :FINAL deprecation, i.e. call a function or access
2112 a variable."))
2114 ;;;; restart definitions
2116 (define-condition abort-failure (control-error) ()
2117 (:report
2118 "An ABORT restart was found that failed to transfer control dynamically."))
2120 (defun abort (&optional condition)
2121 "Transfer control to a restart named ABORT, signalling a CONTROL-ERROR if
2122 none exists."
2123 (invoke-restart (find-restart-or-control-error 'abort condition))
2124 ;; ABORT signals an error in case there was a restart named ABORT
2125 ;; that did not transfer control dynamically. This could happen with
2126 ;; RESTART-BIND.
2127 (error 'abort-failure))
2129 (defun muffle-warning (&optional condition)
2130 "Transfer control to a restart named MUFFLE-WARNING, signalling a
2131 CONTROL-ERROR if none exists."
2132 (invoke-restart (find-restart-or-control-error 'muffle-warning condition)))
2134 (defun try-restart (name condition &rest arguments)
2135 (let ((restart (find-restart name condition)))
2136 (when restart
2137 (apply #'invoke-restart restart arguments))))
2139 (macrolet ((define-nil-returning-restart (name args doc)
2140 `(defun ,name (,@args &optional condition)
2141 ,doc
2142 (try-restart ',name condition ,@args))))
2143 (define-nil-returning-restart continue ()
2144 "Transfer control to a restart named CONTINUE, or return NIL if none exists.")
2145 (define-nil-returning-restart store-value (value)
2146 "Transfer control and VALUE to a restart named STORE-VALUE, or
2147 return NIL if none exists.")
2148 (define-nil-returning-restart use-value (value)
2149 "Transfer control and VALUE to a restart named USE-VALUE, or
2150 return NIL if none exists.")
2151 (define-nil-returning-restart print-unreadably ()
2152 "Transfer control to a restart named SB-EXT:PRINT-UNREADABLY, or
2153 return NIL if none exists."))
2155 ;;; single-stepping restarts
2157 (macrolet ((def (name doc)
2158 `(defun ,name (condition)
2159 ,doc
2160 (invoke-restart (find-restart-or-control-error ',name condition)))))
2161 (def step-continue
2162 "Transfers control to the STEP-CONTINUE restart associated with
2163 the condition, continuing execution without stepping. Signals a
2164 CONTROL-ERROR if the restart does not exist.")
2165 (def step-next
2166 "Transfers control to the STEP-NEXT restart associated with the
2167 condition, executing the current form without stepping and continuing
2168 stepping with the next form. Signals CONTROL-ERROR if the restart does
2169 not exist.")
2170 (def step-into
2171 "Transfers control to the STEP-INTO restart associated with the
2172 condition, stepping into the current form. Signals a CONTROL-ERROR if
2173 the restart does not exist."))
2175 ;;; Compiler macro magic
2177 (define-condition compiler-macro-keyword-problem ()
2178 ((argument :initarg :argument :reader compiler-macro-keyword-argument))
2179 (:report (lambda (condition stream)
2180 (format stream "~@<Argument ~S in keyword position is not ~
2181 a self-evaluating symbol, preventing compiler-macro ~
2182 expansion.~@:>"
2183 (compiler-macro-keyword-argument condition)))))
2185 ;; After (or if) we deem this the optimal name for this condition,
2186 ;; it should be exported from SB-EXT so that people can muffle it.
2187 (define-condition sb-c:inlining-dependency-failure (simple-style-warning) ())
2190 (define-condition layout-invalid (type-error)
2192 (:report
2193 (lambda (condition stream)
2194 (format stream
2195 "~@<invalid structure layout: ~
2196 ~2I~_A test for class ~4I~_~S ~
2197 ~2I~_was passed the obsolete instance ~4I~_~S~:>"
2198 (classoid-proper-name (type-error-expected-type condition))
2199 (type-error-datum condition)))))
2201 (define-condition case-failure (type-error)
2202 ((name :reader case-failure-name :initarg :name)
2203 ;; This is an internal symbol of SB-KERNEL, so I can't imagine that anyone
2204 ;; expects an invariant that it be a list.
2205 (possibilities :reader case-failure-possibilities :initarg :possibilities))
2206 (:report
2207 (lambda (condition stream)
2208 (let ((possibilities (case-failure-possibilities condition)))
2209 (if (symbolp possibilities)
2210 (report-general-type-error condition stream)
2211 (let ((*print-escape* t))
2212 (format stream "~@<~S fell through ~S expression.~@[ ~
2213 ~:_Wanted one of (~/pprint-fill/).~]~:>"
2214 (type-error-datum condition)
2215 (case-failure-name condition)
2216 (case-failure-possibilities condition))))))))
2218 (define-condition compiled-program-error (program-error)
2219 ((message :initarg :message :reader program-error-message)
2220 (source :initarg :source :reader program-error-source))
2221 (:report (lambda (condition stream)
2222 (format stream "Execution of a form compiled with errors.~%~
2223 Form:~% ~A~%~
2224 Compile-time error:~% ~A"
2225 (program-error-source condition)
2226 (program-error-message condition)))))
2228 (define-condition simple-control-error (simple-condition control-error) ())
2230 (define-condition simple-file-error (simple-condition file-error)
2231 ((message :initarg :message :reader simple-file-error-message :initform nil))
2232 (:report
2233 (lambda (condition stream)
2234 (format stream "~@<~?~@[: ~2I~_~A~]~@:>"
2235 (simple-condition-format-control condition)
2236 (simple-condition-format-arguments condition)
2237 (simple-file-error-message condition)))))
2239 (defun %file-error (pathname &optional datum &rest arguments)
2240 (typecase datum
2241 (format-control (error 'simple-file-error :pathname pathname
2242 :format-control datum
2243 :format-arguments arguments))
2244 (t (apply #'error datum :pathname pathname arguments))))
2246 (define-condition file-exists (simple-file-error) ()
2247 (:report
2248 (lambda (condition stream)
2249 (format stream "~@<The file ~S already exists~@[: ~2I~_~A~]~@:>"
2250 (file-error-pathname condition)
2251 (simple-file-error-message condition)))))
2253 (define-condition file-does-not-exist (simple-file-error) ()
2254 (:report
2255 (lambda (condition stream)
2256 (format stream "~@<The file ~S does not exist~@[: ~2I~_~A~]~@:>"
2257 (file-error-pathname condition)
2258 (simple-file-error-message condition)))))
2260 (define-condition delete-file-error (simple-file-error) ()
2261 (:report
2262 (lambda (condition stream)
2263 (format stream "~@<Could not delete the file ~S~@[: ~2I~_~A~]~@:>"
2264 (file-error-pathname condition)
2265 (simple-file-error-message condition)))))
2267 (define-condition simple-stream-error (simple-condition stream-error) ())
2268 (define-condition simple-parse-error (simple-condition parse-error) ())
2270 (define-condition broken-pipe (simple-stream-error) ())
2272 (define-condition character-coding-error (error)
2273 ((external-format :initarg :external-format :reader character-coding-error-external-format)))
2274 (define-condition character-encoding-error (character-coding-error)
2275 ((code :initarg :code :reader character-encoding-error-code)))
2276 (define-condition character-decoding-error (character-coding-error)
2277 ((octets :initarg :octets :reader character-decoding-error-octets)))
2278 (define-condition stream-encoding-error (stream-error character-encoding-error)
2280 (:report
2281 (lambda (c s)
2282 (let ((stream (stream-error-stream c))
2283 (code (character-encoding-error-code c)))
2284 (format s "~@<~S stream encoding error on ~S: ~2I~_~
2285 the character with code ~D cannot be encoded.~@:>"
2286 (character-coding-error-external-format c)
2287 stream
2288 code)))))
2289 (define-condition stream-decoding-error (stream-error character-decoding-error)
2291 (:report
2292 (lambda (c s)
2293 (let ((stream (stream-error-stream c))
2294 (octets (character-decoding-error-octets c)))
2295 (format s "~@<~S stream decoding error on ~S: ~2I~_~
2296 the octet sequence ~S cannot be decoded.~@:>"
2297 (character-coding-error-external-format c)
2298 stream
2299 octets)))))
2301 (define-condition c-string-encoding-error (character-encoding-error)
2303 (:report
2304 (lambda (c s)
2305 (format s "~@<~S c-string encoding error: ~2I~_~
2306 the character with code ~D cannot be encoded.~@:>"
2307 (character-coding-error-external-format c)
2308 (character-encoding-error-code c)))))
2310 (define-condition c-string-decoding-error (character-decoding-error)
2312 (:report
2313 (lambda (c s)
2314 (format s "~@<~S c-string decoding error: ~2I~_~
2315 the octet sequence ~S cannot be decoded.~@:>"
2316 (character-coding-error-external-format c)
2317 (character-decoding-error-octets c)))))
2320 (define-condition stack-allocated-object-overflows-stack (storage-condition)
2321 ((size :initarg :size :reader stack-allocated-object-overflows-stack-size))
2322 (:report
2323 (lambda (condition stream)
2324 (format stream
2325 "~@<Stack allocating object of size ~D bytes exceeds the ~
2326 remaining space left on the control stack.~@:>"
2327 (stack-allocated-object-overflows-stack-size condition)))))
2329 (define-condition control-stack-exhausted (storage-condition)
2331 (:report
2332 (lambda (condition stream)
2333 (declare (ignore condition))
2334 (format stream
2335 ;; no pretty-printing, because that would use a lot of stack.
2336 "Control stack exhausted (no more space for function call frames).
2337 This is probably due to heavily nested or infinitely recursive function
2338 calls, or a tail call that SBCL cannot or has not optimized away.
2340 PROCEED WITH CAUTION."))))
2342 (define-condition binding-stack-exhausted (storage-condition)
2344 (:report
2345 (lambda (condition stream)
2346 (declare (ignore condition))
2347 (format stream
2348 ;; no pretty-printing, because that would use a lot of stack.
2349 "Binding stack exhausted.
2351 PROCEED WITH CAUTION."))))
2353 (define-condition alien-stack-exhausted (storage-condition)
2355 (:report
2356 (lambda (condition stream)
2357 (declare (ignore condition))
2358 (format stream
2359 ;; no pretty-printing, because that would use a lot of stack.
2360 "Alien stack exhausted.
2362 PROCEED WITH CAUTION."))))
2364 (define-condition heap-exhausted-error (storage-condition)
2366 (:report
2367 (lambda (condition stream)
2368 (declare (ignore condition))
2369 (declare (special *heap-exhausted-error-available-bytes*
2370 *heap-exhausted-error-requested-bytes*))
2371 ;; See comments in interr.lisp -- there is a method to this madness.
2372 (if (and (boundp '*heap-exhausted-error-available-bytes*)
2373 (boundp '*heap-exhausted-error-requested-bytes*))
2374 (format stream
2375 ;; no pretty-printing, because that will use a lot of heap.
2376 "Heap exhausted (no more space for allocation).
2377 ~D bytes available, ~D requested.
2379 PROCEED WITH CAUTION."
2380 *heap-exhausted-error-available-bytes*
2381 *heap-exhausted-error-requested-bytes*)
2382 (format stream
2383 "A ~S condition without bindings for heap statistics. (If
2384 you did not expect to see this message, please report it."
2385 'heap-exhausted-error)))))
2387 (define-condition system-condition (condition)
2388 ((address :initarg :address :reader system-condition-address :initform nil)
2389 (context :initarg :context :reader system-condition-context :initform nil)))
2391 (define-condition breakpoint-error (system-condition error) ()
2392 (:report
2393 (lambda (condition stream)
2394 (format stream "Unhandled breakpoint/trap at #x~X."
2395 (system-condition-address condition)))))
2397 (define-condition interactive-interrupt (system-condition serious-condition) ()
2398 (:report
2399 (lambda (condition stream)
2400 (format stream "Interactive interrupt at #x~X."
2401 (system-condition-address condition)))))
2404 ;;;; Condition reporting:
2406 ;;; FIXME: ANSI's definition of DEFINE-CONDITION says
2407 ;;; Condition reporting is mediated through the PRINT-OBJECT method
2408 ;;; for the condition type in question, with *PRINT-ESCAPE* always
2409 ;;; being nil. Specifying (:REPORT REPORT-NAME) in the definition of
2410 ;;; a condition type C is equivalent to:
2411 ;;; (defmethod print-object ((x c) stream)
2412 ;;; (if *print-escape* (call-next-method) (report-name x stream)))
2413 ;;; The current code doesn't seem to quite match that.
2414 (defmethod print-object ((object condition) stream)
2415 (declare (notinline classoid-of)) ; to avoid can't inline warning. speed irrelevant here
2416 (cond
2417 ((not *print-escape*)
2418 ;; KLUDGE: A comment from CMU CL here said
2419 ;; 7/13/98 BUG? CPL is not sorted and results here depend on order of
2420 ;; superclasses in define-condition call!
2421 (funcall (or (some #'condition-classoid-report
2422 (condition-classoid-cpl (classoid-of object)))
2423 (error "no REPORT? shouldn't happen!"))
2424 object stream))
2425 ((and (typep object 'simple-condition)
2426 (condition-slot-value object 'format-control))
2427 (print-unreadable-object (object stream :type t :identity t)
2428 (write (simple-condition-format-control object)
2429 :stream stream :lines 1)))
2431 (print-unreadable-object (object stream :type t :identity t)))))
2434 (defun assert-error (assertion &rest rest)
2435 (let* ((rest rest)
2436 (n-args-and-values (if (fixnump (car rest))
2437 (* (pop rest) 2)
2439 (args-and-values (subseq rest 0 n-args-and-values)))
2440 (destructuring-bind (&optional places datum &rest arguments)
2441 (subseq rest n-args-and-values)
2442 (let ((cond (if datum
2443 (apply #'coerce-to-condition
2444 datum 'simple-error 'error arguments)
2445 (make-condition
2446 'simple-error
2447 :format-control "~@<The assertion ~S failed~:[.~:; ~
2448 with ~:*~{~S = ~S~^, ~}.~]~:@>"
2449 :format-arguments (list assertion args-and-values)))))
2450 (restart-case
2451 (error cond)
2452 (continue ()
2453 :report (lambda (stream)
2454 (format stream "Retry assertion")
2455 (if places
2456 (format stream " with new value~P for ~{~S~^, ~}."
2457 (length places) places)
2458 (format stream ".")))
2459 nil))))))
2461 ;;; READ-EVALUATED-FORM is used as the interactive method for restart cases
2462 ;;; setup by the Common Lisp "casing" (e.g., CCASE and CTYPECASE) macros
2463 ;;; and by CHECK-TYPE.
2464 (defun read-evaluated-form (&optional (prompt-control nil promptp)
2465 &rest prompt-args)
2466 (apply #'format *query-io*
2467 (if promptp prompt-control "~&Enter a form to be evaluated: ")
2468 prompt-args)
2469 (finish-output *query-io*)
2470 (list (eval (read *query-io*))))
2472 (defun read-evaluated-form-of-type (type &optional (prompt-control nil promptp)
2473 &rest prompt-args)
2474 (loop (apply #'format *query-io*
2475 (if promptp prompt-control "~&Enter a form evaluating to a value of type ~a: ")
2476 (if promptp prompt-args (list type)))
2477 (finish-output *query-io*)
2478 (let ((result (eval (read *query-io*))))
2479 (when (typep result type)
2480 (return (list result)))
2481 (format *query-io* "~s is not of type ~s" result type))))
2483 ;;; Same as above but returns multiple values
2484 (defun mv-read-evaluated-form (&optional (prompt-control nil promptp)
2485 &rest prompt-args)
2486 (apply #'format *query-io*
2487 (if promptp prompt-control "~&Enter a form to be evaluated: ")
2488 prompt-args)
2489 (finish-output *query-io*)
2490 (multiple-value-list (eval (read *query-io*))))
2492 (defun check-type-error (place place-value type &optional type-string)
2493 (let ((condition
2494 (make-condition
2495 'simple-type-error
2496 :datum place-value
2497 :expected-type type
2498 :format-control
2499 "The value of ~S is ~S, which is not ~:[of type ~S~;~:*~A~]."
2500 :format-arguments (list place place-value type-string type))))
2501 (restart-case (error condition)
2502 (store-value (value)
2503 :report (lambda (stream)
2504 (format stream "Supply a new value for ~S." place))
2505 :interactive read-evaluated-form
2506 value))))
2508 (define-error-wrapper etypecase-failure (value keys)
2509 (error 'case-failure
2510 :name 'etypecase
2511 :datum value
2512 :expected-type (if (symbolp keys) keys `(or ,@keys))
2513 :possibilities keys))
2515 (define-error-wrapper ecase-failure (value keys)
2516 ;; inline definition not seen yet. Can't move this file later
2517 ;; in build because **<foo>-clusters** are needed early.
2518 (declare (notinline coerce))
2519 (when (vectorp keys) (setq keys (coerce keys 'list)))
2520 (error 'case-failure
2521 :name 'ecase
2522 :datum value
2523 :expected-type `(member ,@keys)
2524 :possibilities keys))
2526 (defun case-body-error (name keyform keyform-value expected-type keys)
2527 (restart-case
2528 (error 'case-failure
2529 :name name
2530 :datum keyform-value
2531 :expected-type expected-type
2532 :possibilities keys)
2533 (store-value (value)
2534 :report (lambda (stream)
2535 (format stream "Supply a new value for ~S." keyform))
2536 :interactive read-evaluated-form
2537 value)))