0.pre7.127:
[sbcl.git] / src / code / target-error.lisp
1 ;;;; that part of the condition system which can or should come early
2 ;;;; (mostly macro-related)
3
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.
12
13 (in-package "SB!KERNEL")
14 \f
15 ;;;; restarts
16
17 ;;; a list of lists of restarts
18 (defvar *restart-clusters* '())
19
20 ;;; an ALIST (condition . restarts) which records the restarts currently
21 ;;; associated with Condition
22 (defvar *condition-restarts* ())
23
24 (defstruct (restart (:copier nil) (:predicate nil))
25   (name (missing-arg) :type symbol :read-only t)
26   function
27   report-function
28   interactive-function
29   (test-fun (lambda (cond) (declare (ignore cond)) t)))
30 (def!method print-object ((restart restart) stream)
31   (if *print-escape*
32       (print-unreadable-object (restart stream :type t :identity t)
33         (prin1 (restart-name restart) stream))
34       (restart-report restart stream)))
35
36 (defun compute-restarts (&optional condition)
37   #!+sb-doc
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."
42   (let ((associated ())
43         (other ()))
44     (dolist (alist *condition-restarts*)
45       (if (eq (car alist) condition)
46           (setq associated (cdr alist))
47           (setq other (append (cdr alist) other))))
48     (collect ((res))
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))
55             (res restart))))
56       (res))))
57
58 #!+sb-doc
59 (setf (fdocumentation 'restart-name 'function)
60       "Return the name of the given restart object.")
61
62 (defun restart-report (restart stream)
63   (funcall (or (restart-report-function restart)
64                (let ((name (restart-name restart)))
65                  (lambda (stream)
66                    (if name (format stream "~S" name)
67                        (format stream "~S" restart)))))
68            stream))
69
70 (defmacro with-condition-restarts (condition-form restarts-form &body body)
71   #!+sb-doc
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))
80                     (cons ,n-cond
81                           (append ,restarts-form
82                                   (cdr (assoc ,n-cond *condition-restarts*)))))
83                   *condition-restarts*)))
84        ,@body)))
85
86 (defmacro restart-bind (bindings &body forms)
87   #!+sb-doc
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*
92           (cons (list
93                  ,@(mapcar (lambda (binding)
94                              (unless (or (car binding)
95                                          (member :report-function
96                                                  binding
97                                                  :test #'eq))
98                                (warn "Unnamed restart does not have a ~
99                                         report function: ~S"
100                                      binding))
101                              `(make-restart :name ',(car binding)
102                                             :function ,(cadr binding)
103                                             ,@(cddr binding)))
104                            bindings))
105                 *restart-clusters*)))
106      ,@forms))
107
108 (defun find-restart (name &optional condition)
109   #!+sb-doc
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."
115   (find-if (lambda (x)
116              (or (eq x name)
117                  (eq (restart-name x) name)))
118            (compute-restarts condition)))
119
120 (defun invoke-restart (restart &rest values)
121   #!+sb-doc
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)))
127     (unless real-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)))
133
134 (defun invoke-restart-interactively (restart)
135   #!+sb-doc
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)))
141     (unless real-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)
152                  '())))))
153
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)))
159     (if (consp exp)
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
164                                     ,(first args)
165                                     (list ,@(rest args))
166                                     ',(case name
167                                         (warn 'simple-warning)
168                                         (signal 'simple-condition)
169                                         (t 'simple-error))
170                                     ',name)))
171                 `(with-condition-restarts
172                      ,n-cond
173                      (list ,@(mapcar (lambda (da)
174                                        `(find-restart ',(nth 0 da)))
175                                      data))
176                    ,(if (eq name 'cerror)
177                         `(cerror ,(second expression) ,n-cond)
178                         `(,name ,n-cond))))
179               expression))
180         expression)))
181 ) ; EVAL-WHEN
182
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)
186   #!+sb-doc
187   "(RESTART-CASE form
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
194    the new restarts."
195   (flet ((transform-keywords (&key report interactive test)
196            (let ((result '()))
197              (when report
198                (setq result (list* (if (stringp report)
199                                        `#'(lambda (stream)
200                                             (write-string ,report stream))
201                                        `#',report)
202                                    :report-function
203                                    result)))
204              (when interactive
205                (setq result (list* `#',interactive
206                                    :interactive-function
207                                    result)))
208              (when test
209                (setq result (list* `#',test :test-fun result)))
210              (nreverse 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))
217           (temp-var (gensym))
218           (data
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.
227                       ;;   -- WHN 19990925
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~]."
232                                    temp))
233                           (let* ((key-vars (ldiff names temp))
234                                  (keywords (mapcar #'keywordicate key-vars))
235                                  (key-var (gensym))
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
241                                                             ,keyword)))
242                                              key-vars keywords)
243                                  ,@forms))))))
244              (mapcar (lambda (clause)
245                        (with-keyword-pairs ((report interactive test
246                                                     &rest forms)
247                                             (cddr clause))
248                          (list (car clause) ;name=0
249                                (gensym) ;tag=1
250                                (transform-keywords :report report ;keywords=2
251                                                    :interactive interactive
252                                                    :test test)
253                                (cadr clause) ;bvl=3
254                                forms))) ;body=4
255                    clauses))))
256       `(block ,block-tag
257          (let ((,temp-var nil))
258            (tagbody
259             (restart-bind
260                 ,(mapcar (lambda (datum)
261                            (let ((name (nth 0 datum))
262                                  (tag  (nth 1 datum))
263                                  (keys (nth 2 datum)))
264                              `(,name #'(lambda (&rest temp)
265                                          (setq ,temp-var temp)
266                                          (go ,tag))
267                                      ,@keys)))
268                          data)
269               (return-from ,block-tag
270                            ,(munge-restart-case-expression expression data)))
271             ,@(mapcan (lambda (datum)
272                         (let ((tag  (nth 1 datum))
273                               (bvl  (nth 3 datum))
274                               (body (nth 4 datum)))
275                           (list tag
276                                 `(return-from ,block-tag
277                                    (apply (lambda ,bvl ,@body)
278                                           ,temp-var)))))
279                       data)))))))
280
281 (defmacro with-simple-restart ((restart-name format-string
282                                              &rest format-arguments)
283                                &body forms)
284   #!+sb-doc
285   "(WITH-SIMPLE-RESTART (restart-name format-string format-arguments)
286    body)
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."
290   `(restart-case
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))
294      (,restart-name ()
295         :report (lambda (stream)
296                   (format stream ,format-string ,@format-arguments))
297       (values nil t))))
298 \f
299 ;;;; HANDLER-BIND
300
301 (defvar *handler-clusters* nil)
302
303 (defmacro handler-bind (bindings &body forms)
304   #!+sb-doc
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)))
312                               bindings)))
313     (when member-if
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)))
317                                 bindings))
318                 *handler-clusters*)))
319      (multiple-value-prog1
320          (progn
321            ,@forms)
322        ;; Wait for any float exceptions.
323        #!+x86 (float-wait))))
324 \f
325 ;;;; HANDLER-CASE
326
327 (defmacro handler-case (form &rest clauses)
328   "(HANDLER-CASE form
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
334    var specification."
335
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
342   ;;    (DEFUN FOO1I ()
343   ;;      (IF (NOT (IGNORE-ERRORS
344   ;;                 (MAKE-PATHNAME :HOST "FOO"
345   ;;                                :DIRECTORY "!BLA"
346   ;;                                :NAME "BAR")))
347   ;;          (PRINT "OK")
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
356   ;;
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)))
362     (if no-error-clause
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))
381                                       clauses)))
382           `(let ((,outer-tag (cons nil nil))
383                  (,inner-tag (cons nil nil))
384                  ,var ,tag-var)
385              ;; FIXME: should be (DECLARE (IGNORABLE ,VAR))
386              ,var                       ;ignoreable
387              (catch ,outer-tag
388                (catch ,inner-tag
389                  (throw ,outer-tag
390                         (handler-bind
391                             ,(mapcar (lambda (tagged-clause)
392                                        (destructuring-bind
393                                            (tag typespec args &body body)
394                                            tagged-clause
395                                          (declare (ignore body))
396                                          `(,typespec
397                                            (lambda (temp)
398                                              ,(if args
399                                                   `(setq ,var temp)
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)))))
404                                      tagged-clauses)
405                           ,form)))
406                (case ,tag-var
407                  ,@(mapcar (lambda (tagged-clause)
408                              (destructuring-bind
409                                  (tag typespec args &body body)
410                                  tagged-clause
411                                (declare (ignore typespec))
412                                `(,tag
413                                  ,@(if args
414                                        (destructuring-bind (arg) args
415                                          `((let ((,arg ,var))
416                                              ,@body)))
417                                        body))))
418                            tagged-clauses)))))))
419   #+nil ; MNA's patched version -- see FIXME above
420   (let ((no-error-clause (assoc ':no-error cases)))
421     (if no-error-clause
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)))))))
430         (let ((tag (gensym))
431               (var (gensym))
432               (annotated-cases (mapcar (lambda (case) (cons (gensym) case))
433                                        cases)))
434           `(block ,tag
435              (let ((,var nil))
436                (declare (ignorable ,var))
437                (tagbody
438                 (handler-bind
439                     ,(mapcar (lambda (annotated-case)
440                                (list (cadr annotated-case)
441                                      `(lambda (temp)
442                                         ,(if (caddr annotated-case)
443                                              `(setq ,var temp)
444                                              '(declare (ignore temp)))
445                                         (go ,(car annotated-case)))))
446                              annotated-cases)
447                   (return-from ,tag
448                     #!-x86 ,form
449                     #!+x86 (multiple-value-prog1 ,form
450                              ;; Need to catch FP errors here!
451                              (float-wait))))
452                 ,@(mapcan
453                    (lambda (annotated-case)
454                      (list (car annotated-case)
455                            (let ((body (cdddr annotated-case)))
456                              `(return-from
457                                   ,tag
458                                 ,(cond ((caddr annotated-case)
459                                         `(let ((,(caaddr annotated-case)
460                                                 ,var))
461                                            ,@body))
462                                        ((not (cdr body))
463                                         (car body))
464                                        (t
465                                         `(progn ,@body)))))))
466                    annotated-cases))))))))
467 \f
468 ;;;; helper functions for restartable error handling which couldn't be
469 ;;;; defined 'til now 'cause they use the RESTART-CASE macro
470
471 (defun assert-error (assertion places datum &rest arguments)
472   (let ((cond (if datum
473                 (coerce-to-condition datum
474                                                     arguments
475                                                     'simple-error
476                                                     'error)
477                 (make-condition 'simple-error
478                                 :format-control "The assertion ~S failed."
479                                 :format-arguments (list assertion)))))
480     (restart-case
481         (error cond)
482       (continue ()
483                 :report (lambda (stream)
484                           (format stream "Retry assertion")
485                           (if places
486                               (format stream
487                                       " with new value~P for ~{~S~^, ~}."
488                                       (length places)
489                                       places)
490                               (format stream ".")))
491                 nil))))
492
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*))))
499
500 (defun check-type-error (place place-value type type-string)
501   (let ((cond (if type-string
502                   (make-condition 'simple-type-error
503                                   :datum place
504                                   :expected-type type
505                                   :format-control
506                                   "The value of ~S is ~S, which is not ~A."
507                                   :format-arguments (list place
508                                                           place-value
509                                                           type-string))
510                   (make-condition 'simple-type-error
511                                   :datum place
512                                   :expected-type type
513                                   :format-control
514                           "The value of ~S is ~S, which is not of type ~S."
515                                   :format-arguments (list place
516                                                           place-value
517                                                           type)))))
518     (restart-case (error cond)
519       (store-value (value)
520         :report (lambda (stream)
521                   (format stream "Supply a new value for ~S." place))
522         :interactive read-evaluated-form
523         value))))
524
525 (defun case-body-error (name keyform keyform-value expected-type keys)
526   (restart-case
527       (error 'case-failure
528              :name name
529              :datum keyform-value
530              :expected-type expected-type
531              :possibilities keys)
532     (store-value (value)
533       :report (lambda (stream)
534                 (format stream "Supply a new value for ~S." keyform))
535       :interactive read-evaluated-form
536       value)))