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
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")
17 ;;; a list of lists of restarts
18 (defvar *restart-clusters* '())
20 ;;; an ALIST (condition . restarts) which records the restarts currently
21 ;;; associated with Condition
22 (defvar *condition-restarts* ())
24 (defstruct (restart (:copier nil) (:predicate nil))
25 (name (missing-arg) :type symbol :read-only t)
29 (test-fun (lambda (cond) (declare (ignore cond)) t)))
30 (def!method print-object ((restart restart) stream)
32 (print-unreadable-object (restart stream :type t :identity t)
33 (prin1 (restart-name restart) stream))
34 (restart-report restart stream)))
36 (defun compute-restarts (&optional condition)
38 "Return a list of all the currently active restarts ordered from most
39 recently established to less recently established. If CONDITION is
40 specified, then only restarts associated with CONDITION (or with no
41 condition) will be returned."
44 (dolist (alist *condition-restarts*)
45 (if (eq (car alist) condition)
46 (setq associated (cdr alist))
47 (setq other (append (cdr alist) other))))
49 (dolist (restart-cluster *restart-clusters*)
50 (dolist (restart restart-cluster)
51 (when (and (or (not condition)
52 (member restart associated)
53 (not (member restart other)))
54 (funcall (restart-test-fun restart) condition))
59 (setf (fdocumentation 'restart-name 'function)
60 "Return the name of the given restart object.")
62 (defun restart-report (restart stream)
63 (funcall (or (restart-report-function restart)
64 (let ((name (restart-name restart)))
66 (if name (format stream "~S" name)
67 (format stream "~S" restart)))))
70 (defmacro with-condition-restarts (condition-form restarts-form &body body)
72 "WITH-CONDITION-RESTARTS Condition-Form Restarts-Form Form*
73 Evaluates the Forms in a dynamic environment where the restarts in the list
74 Restarts-Form are associated with the condition returned by Condition-Form.
75 This allows FIND-RESTART, etc., to recognize restarts that are not related
76 to the error currently being debugged. See also RESTART-CASE."
77 (let ((n-cond (gensym)))
78 `(let ((*condition-restarts*
79 (cons (let ((,n-cond ,condition-form))
81 (append ,restarts-form
82 (cdr (assoc ,n-cond *condition-restarts*)))))
83 *condition-restarts*)))
86 (defmacro restart-bind (bindings &body forms)
88 "Executes forms in a dynamic context where the given restart bindings are
89 in effect. Users probably want to use RESTART-CASE. When clauses contain
90 the same restart name, FIND-RESTART will find the first such clause."
91 `(let ((*restart-clusters*
93 ,@(mapcar (lambda (binding)
94 (unless (or (car binding)
95 (member :report-function
98 (warn "Unnamed restart does not have a ~
101 `(make-restart :name ',(car binding)
102 :function ,(cadr binding)
105 *restart-clusters*)))
108 (defun find-restart (name &optional condition)
110 "Return the first restart named NAME. If NAME names a restart, the restart
111 is returned if it is currently active. If no such restart is found, NIL is
112 returned. It is an error to supply NIL as a name. If CONDITION is specified
113 and not NIL, then only restarts associated with that condition (or with no
114 condition) will be returned."
117 (eq (restart-name x) name)))
118 (compute-restarts condition)))
120 (defun invoke-restart (restart &rest values)
122 "Calls the function associated with the given restart, passing any given
123 arguments. If the argument restart is not a restart or a currently active
124 non-nil restart name, then a control-error is signalled."
125 (/show "entering INVOKE-RESTART" restart)
126 (let ((real-restart (find-restart restart)))
128 (error 'simple-control-error
129 :format-control "Restart ~S is not active."
130 :format-arguments (list restart)))
131 (/show (restart-name real-restart))
132 (apply (restart-function real-restart) values)))
134 (defun invoke-restart-interactively (restart)
136 "Calls the function associated with the given restart, prompting for any
137 necessary arguments. If the argument restart is not a restart or a
138 currently active non-nil restart name, then a control-error is signalled."
139 (/show "entering INVOKE-RESTART-INTERACTIVELY" restart)
140 (let ((real-restart (find-restart restart)))
142 (error 'simple-control-error
143 :format-control "Restart ~S is not active."
144 :format-arguments (list restart)))
145 (/show (restart-name real-restart))
146 (/show0 "falling through to APPLY of RESTART-FUNCTION")
147 (apply (restart-function real-restart)
148 (let ((interactive-function
149 (restart-interactive-function real-restart)))
150 (if interactive-function
151 (funcall interactive-function)
154 (eval-when (:compile-toplevel :load-toplevel :execute)
155 ;;; Wrap the RESTART-CASE expression in a WITH-CONDITION-RESTARTS if
156 ;;; appropriate. Gross, but it's what the book seems to say...
157 (defun munge-restart-case-expression (expression data)
158 (let ((exp (macroexpand expression)))
160 (let* ((name (car exp))
161 (args (if (eq name 'cerror) (cddr exp) (cdr exp))))
162 (if (member name '(signal error cerror warn))
163 (once-only ((n-cond `(coerce-to-condition
167 (warn 'simple-warning)
168 (signal 'simple-condition)
171 `(with-condition-restarts
173 (list ,@(mapcar (lambda (da)
174 `(find-restart ',(nth 0 da)))
176 ,(if (eq name 'cerror)
177 `(cerror ,(second expression) ,n-cond)
183 ;;; FIXME: I did a fair amount of rearrangement of this code in order to
184 ;;; get WITH-KEYWORD-PAIRS to work cleanly. This code should be tested..
185 (defmacro restart-case (expression &body clauses)
188 {(case-name arg-list {keyword value}* body)}*)
189 The form is evaluated in a dynamic context where the clauses have special
190 meanings as points to which control may be transferred (see INVOKE-RESTART).
191 When clauses contain the same case-name, FIND-RESTART will find the first
192 such clause. If Expression is a call to SIGNAL, ERROR, CERROR or WARN (or
193 macroexpands into such) then the signalled condition will be associated with
195 (flet ((transform-keywords (&key report interactive test)
198 (setq result (list* (if (stringp report)
200 (write-string ,report stream))
205 (setq result (list* `#',interactive
206 :interactive-function
209 (setq result (list* `#',test :test-fun result)))
211 (parse-keyword-pairs (list keys)
212 (do ((l list (cddr l))
213 (k '() (list* (cadr l) (car l) k)))
214 ((or (null l) (not (member (car l) keys)))
215 (values (nreverse k) l)))))
216 (let ((block-tag (gensym))
219 (macrolet (;; KLUDGE: This started as an old DEFMACRO
220 ;; WITH-KEYWORD-PAIRS general utility, which was used
221 ;; only in this one place in the code. It was translated
222 ;; literally into this MACROLET in order to avoid some
223 ;; cross-compilation bootstrap problems. It would almost
224 ;; certainly be clearer, and it would certainly be more
225 ;; concise, to do a more idiomatic translation, merging
226 ;; this with the TRANSFORM-KEYWORDS logic above.
228 (with-keyword-pairs ((names expression) &body forms)
229 (let ((temp (member '&rest names)))
230 (unless (= (length temp) 2)
231 (error "&REST keyword is ~:[missing~;misplaced~]."
233 (let* ((key-vars (ldiff names temp))
234 (keywords (mapcar #'keywordicate key-vars))
236 (rest-var (cadr temp)))
237 `(multiple-value-bind (,key-var ,rest-var)
238 (parse-keyword-pairs ,expression ',keywords)
239 (let ,(mapcar (lambda (var keyword)
240 `(,var (getf ,key-var
244 (mapcar (lambda (clause)
245 (with-keyword-pairs ((report interactive test
248 (list (car clause) ;name=0
250 (transform-keywords :report report ;keywords=2
251 :interactive interactive
257 (let ((,temp-var nil))
260 ,(mapcar (lambda (datum)
261 (let ((name (nth 0 datum))
263 (keys (nth 2 datum)))
264 `(,name #'(lambda (&rest temp)
265 (setq ,temp-var temp)
269 (return-from ,block-tag
270 ,(munge-restart-case-expression expression data)))
271 ,@(mapcan (lambda (datum)
272 (let ((tag (nth 1 datum))
274 (body (nth 4 datum)))
276 `(return-from ,block-tag
277 (apply (lambda ,bvl ,@body)
281 (defmacro with-simple-restart ((restart-name format-string
282 &rest format-arguments)
285 "(WITH-SIMPLE-RESTART (restart-name format-string format-arguments)
287 If restart-name is not invoked, then all values returned by forms are
288 returned. If control is transferred to this restart, it immediately
289 returns the values NIL and T."
291 ;; If there's just one body form, then don't use PROGN. This allows
292 ;; RESTART-CASE to "see" calls to ERROR, etc.
293 ,(if (= (length forms) 1) (car forms) `(progn ,@forms))
295 :report (lambda (stream)
296 (format stream ,format-string ,@format-arguments))
301 (defvar *handler-clusters* nil)
303 (defmacro handler-bind (bindings &body forms)
305 "(HANDLER-BIND ( {(type handler)}* ) body)
306 Executes body in a dynamic context where the given handler bindings are
307 in effect. Each handler must take the condition being signalled as an
308 argument. The bindings are searched first to last in the event of a
309 signalled condition."
310 (let ((member-if (member-if (lambda (x)
311 (not (proper-list-of-length-p x 2)))
314 (error "ill-formed handler binding: ~S" (first member-if))))
315 `(let ((*handler-clusters*
316 (cons (list ,@(mapcar (lambda (x) `(cons ',(car x) ,(cadr x)))
318 *handler-clusters*)))
319 (multiple-value-prog1
322 ;; Wait for any float exceptions.
323 #!+x86 (float-wait))))
327 (defmacro handler-case (form &rest clauses)
329 { (type ([var]) body) }* )
330 Execute FORM in a context with handlers established for the condition
331 types. A peculiar property allows type to be :no-error. If such a clause
332 occurs, and form returns normally, all its values are passed to this clause
333 as if by MULTIPLE-VALUE-CALL. The :NO-ERROR clause accepts more than one
336 ;; FIXME: This old SBCL code uses multiple nested THROW/CATCH
337 ;; operations, which seems like an ugly way to handle lexical
338 ;; nonlocal exit. MNA sbcl-devel 2001-07-17 provided a patch
339 ;; (included below this form, but #+NIL'ed out) to switch over to
340 ;; RETURN-FROM, which seems like basically a better idea.
341 ;; Unfortunately when using his patch, this reasonable code
343 ;; (IF (NOT (IGNORE-ERRORS
344 ;; (MAKE-PATHNAME :HOST "FOO"
348 ;; (ERROR "NOTUNLESSNOT")))
349 ;; fails (doing ERROR "NOTUNLESSNOT" when it should PRINT "OK"
350 ;; instead). I think this may not be a bug in MNA's patch, but
351 ;; instead in the rest of the compiler (e.g. handling of RETURN-FROM)
352 ;; but whatever the reason. (I noticed this problem in
353 ;; sbcl-0.pre7.14.flaky4.11, and reverted to the old code at that point.
354 ;; The problem also occurs at least in sbcl-0.6.12.59 and
355 ;; sbcl-0.6.13.) -- WHN
357 ;; Note also: I think the old nested THROW/CATCH version became
358 ;; easier to read once I converted it to use DESTRUCTURING-BIND and
359 ;; mnemonic names, and it would probably be a useful to do that to
360 ;; the RETURN-FROM version when/if it's adopted.
361 (let ((no-error-clause (assoc ':no-error clauses)))
363 (let ((normal-return (make-symbol "normal-return"))
364 (error-return (make-symbol "error-return")))
365 `(block ,error-return
366 (multiple-value-call #'(lambda ,@(cdr no-error-clause))
367 (block ,normal-return
368 (return-from ,error-return
369 (handler-case (return-from ,normal-return ,form)
370 ;; FIXME: What if there's more than one :NO-ERROR
371 ;; clause? The code here and above doesn't seem
372 ;; either to remove both of them or to signal
373 ;; a good error, so it's probably wrong.
374 ,@(remove no-error-clause clauses)))))))
375 (let ((var (gensym "HC-VAR-"))
376 (outer-tag (gensym "OUTER-HC-TAG-"))
377 (inner-tag (gensym "INNER-HC-TAG-"))
378 (tag-var (gensym "HC-TAG-VAR-"))
379 (tagged-clauses (mapcar (lambda (clause)
380 (cons (gensym "HC-TAG-") clause))
382 `(let ((,outer-tag (cons nil nil))
383 (,inner-tag (cons nil nil))
385 ;; FIXME: should be (DECLARE (IGNORABLE ,VAR))
391 ,(mapcar (lambda (tagged-clause)
393 (tag typespec args &body body)
395 (declare (ignore body))
400 '(declare (ignore temp)))
401 (setf ,tag-var ',tag)
402 (/show "THROWing INNER-TAG from HANDLER-BIND closure for" ',typespec)
403 (throw ,inner-tag nil)))))
407 ,@(mapcar (lambda (tagged-clause)
409 (tag typespec args &body body)
411 (declare (ignore typespec))
414 (destructuring-bind (arg) args
418 tagged-clauses)))))))
419 #+nil ; MNA's patched version -- see FIXME above
420 (let ((no-error-clause (assoc ':no-error cases)))
422 (let ((normal-return (make-symbol "normal-return"))
423 (error-return (make-symbol "error-return")))
424 `(block ,error-return
425 (multiple-value-call (lambda ,@(cdr no-error-clause))
426 (block ,normal-return
427 (return-from ,error-return
428 (handler-case (return-from ,normal-return ,form)
429 ,@(remove no-error-clause cases)))))))
432 (annotated-cases (mapcar (lambda (case) (cons (gensym) case))
436 (declare (ignorable ,var))
439 ,(mapcar (lambda (annotated-case)
440 (list (cadr annotated-case)
442 ,(if (caddr annotated-case)
444 '(declare (ignore temp)))
445 (go ,(car annotated-case)))))
449 #!+x86 (multiple-value-prog1 ,form
450 ;; Need to catch FP errors here!
453 (lambda (annotated-case)
454 (list (car annotated-case)
455 (let ((body (cdddr annotated-case)))
458 ,(cond ((caddr annotated-case)
459 `(let ((,(caaddr annotated-case)
465 `(progn ,@body)))))))
466 annotated-cases))))))))
468 ;;;; helper functions for restartable error handling which couldn't be
469 ;;;; defined 'til now 'cause they use the RESTART-CASE macro
471 (defun assert-error (assertion places datum &rest arguments)
472 (let ((cond (if datum
473 (coerce-to-condition datum
477 (make-condition 'simple-error
478 :format-control "The assertion ~S failed."
479 :format-arguments (list assertion)))))
483 :report (lambda (stream)
484 (format stream "Retry assertion")
487 " with new value~P for ~{~S~^, ~}."
490 (format stream ".")))
493 ;;; READ-EVALUATED-FORM is used as the interactive method for restart cases
494 ;;; setup by the Common Lisp "casing" (e.g., CCASE and CTYPECASE) macros
495 ;;; and by CHECK-TYPE.
496 (defun read-evaluated-form ()
497 (format *query-io* "~&Type a form to be evaluated:~%")
498 (list (eval (read *query-io*))))
500 (defun check-type-error (place place-value type type-string)
501 (let ((cond (if type-string
502 (make-condition 'simple-type-error
506 "The value of ~S is ~S, which is not ~A."
507 :format-arguments (list place
510 (make-condition 'simple-type-error
514 "The value of ~S is ~S, which is not of type ~S."
515 :format-arguments (list place
518 (restart-case (error cond)
520 :report (lambda (stream)
521 (format stream "Supply a new value for ~S." place))
522 :interactive read-evaluated-form
525 (defun case-body-error (name keyform keyform-value expected-type keys)
530 :expected-type expected-type
533 :report (lambda (stream)
534 (format stream "Supply a new value for ~S." keyform))
535 :interactive read-evaluated-form