0.7.12.5:
[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 (missing-arg) :type function)
27   (report-function nil :type (or null function))
28   (interactive-function nil :type (or null function))
29   (test-function (lambda (cond) (declare (ignore cond)) t) :type function))
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-function restart)
55                               condition))
56             (res restart))))
57       (res))))
58
59 #!+sb-doc
60 (setf (fdocumentation 'restart-name 'function)
61       "Return the name of the given restart object.")
62
63 (defun restart-report (restart stream)
64   (funcall (or (restart-report-function restart)
65                (let ((name (restart-name restart)))
66                  (lambda (stream)
67                    (if name (format stream "~S" name)
68                        (format stream "~S" restart)))))
69            stream))
70
71 (defmacro with-condition-restarts (condition-form restarts-form &body body)
72   #!+sb-doc
73   "WITH-CONDITION-RESTARTS Condition-Form Restarts-Form Form*
74    Evaluates the Forms in a dynamic environment where the restarts in the list
75    Restarts-Form are associated with the condition returned by Condition-Form.
76    This allows FIND-RESTART, etc., to recognize restarts that are not related
77    to the error currently being debugged. See also RESTART-CASE."
78   (let ((n-cond (gensym)))
79     `(let ((*condition-restarts*
80             (cons (let ((,n-cond ,condition-form))
81                     (cons ,n-cond
82                           (append ,restarts-form
83                                   (cdr (assoc ,n-cond *condition-restarts*)))))
84                   *condition-restarts*)))
85        ,@body)))
86
87 (defmacro restart-bind (bindings &body forms)
88   #!+sb-doc
89   "Executes forms in a dynamic context where the given restart bindings are
90    in effect. Users probably want to use RESTART-CASE. When clauses contain
91    the same restart name, FIND-RESTART will find the first such clause."
92   `(let ((*restart-clusters*
93           (cons (list
94                  ,@(mapcar (lambda (binding)
95                              (unless (or (car binding)
96                                          (member :report-function
97                                                  binding
98                                                  :test #'eq))
99                                (warn "Unnamed restart does not have a ~
100                                         report function: ~S"
101                                      binding))
102                              `(make-restart :name ',(car binding)
103                                             :function ,(cadr binding)
104                                             ,@(cddr binding)))
105                            bindings))
106                 *restart-clusters*)))
107      ,@forms))
108
109 (defun find-restart (name &optional condition)
110   #!+sb-doc
111   "Return the first restart named NAME. If NAME names a restart, the restart
112    is returned if it is currently active. If no such restart is found, NIL is
113    returned. It is an error to supply NIL as a name. If CONDITION is specified
114    and not NIL, then only restarts associated with that condition (or with no
115    condition) will be returned."
116   (let ((restarts (compute-restarts condition)))
117     (declare (type list restarts))
118     (find-if (lambda (x)
119                (or (eq x name)
120                    (eq (restart-name x) name)))
121              restarts)))
122
123 (defun invoke-restart (restart &rest values)
124   #!+sb-doc
125   "Calls the function associated with the given restart, passing any given
126    arguments. If the argument restart is not a restart or a currently active
127    non-nil restart name, then a control-error is signalled."
128   (/show "entering INVOKE-RESTART" restart)
129   (let ((real-restart (find-restart restart)))
130     (unless real-restart
131       (error 'simple-control-error
132              :format-control "Restart ~S is not active."
133              :format-arguments (list restart)))
134     (/show (restart-name real-restart))
135     (apply (restart-function real-restart) values)))
136
137 (defun invoke-restart-interactively (restart)
138   #!+sb-doc
139   "Calls the function associated with the given restart, prompting for any
140    necessary arguments. If the argument restart is not a restart or a
141    currently active non-nil restart name, then a control-error is signalled."
142   (/show "entering INVOKE-RESTART-INTERACTIVELY" restart)
143   (let ((real-restart (find-restart restart)))
144     (unless real-restart
145       (error 'simple-control-error
146              :format-control "Restart ~S is not active."
147              :format-arguments (list restart)))
148     (/show (restart-name real-restart))
149     (/show0 "falling through to APPLY of RESTART-FUNCTION")
150     (apply (restart-function real-restart)
151            (let ((interactive-function
152                   (restart-interactive-function real-restart)))
153              (if interactive-function
154                  (funcall interactive-function)
155                  '())))))
156
157 (eval-when (:compile-toplevel :load-toplevel :execute)
158 ;;; Wrap the RESTART-CASE expression in a WITH-CONDITION-RESTARTS if
159 ;;; appropriate. Gross, but it's what the book seems to say...
160 (defun munge-restart-case-expression (expression data)
161   (let ((exp (macroexpand expression)))
162     (if (consp exp)
163         (let* ((name (car exp))
164                (args (if (eq name 'cerror) (cddr exp) (cdr exp))))
165           (if (member name '(signal error cerror warn))
166               (once-only ((n-cond `(coerce-to-condition
167                                     ,(first args)
168                                     (list ,@(rest args))
169                                     ',(case name
170                                         (warn 'simple-warning)
171                                         (signal 'simple-condition)
172                                         (t 'simple-error))
173                                     ',name)))
174                 `(with-condition-restarts
175                      ,n-cond
176                      (list ,@(mapcar (lambda (da)
177                                        `(find-restart ',(nth 0 da)))
178                                      data))
179                    ,(if (eq name 'cerror)
180                         `(cerror ,(second expression) ,n-cond)
181                         `(,name ,n-cond))))
182               expression))
183         expression)))
184 ) ; EVAL-WHEN
185
186 ;;; FIXME: I did a fair amount of rearrangement of this code in order to
187 ;;; get WITH-KEYWORD-PAIRS to work cleanly. This code should be tested..
188 (defmacro restart-case (expression &body clauses)
189   #!+sb-doc
190   "(RESTART-CASE form
191    {(case-name arg-list {keyword value}* body)}*)
192    The form is evaluated in a dynamic context where the clauses have special
193    meanings as points to which control may be transferred (see INVOKE-RESTART).
194    When clauses contain the same case-name, FIND-RESTART will find the first
195    such clause. If Expression is a call to SIGNAL, ERROR, CERROR or WARN (or
196    macroexpands into such) then the signalled condition will be associated with
197    the new restarts."
198   (flet ((transform-keywords (&key report interactive test)
199            (let ((result '()))
200              (when report
201                (setq result (list* (if (stringp report)
202                                        `#'(lambda (stream)
203                                             (write-string ,report stream))
204                                        `#',report)
205                                    :report-function
206                                    result)))
207              (when interactive
208                (setq result (list* `#',interactive
209                                    :interactive-function
210                                    result)))
211              (when test
212                (setq result (list* `#',test :test-function result)))
213              (nreverse result)))
214          (parse-keyword-pairs (list keys)
215            (do ((l list (cddr l))
216                 (k '() (list* (cadr l) (car l) k)))
217                ((or (null l) (not (member (car l) keys)))
218                 (values (nreverse k) l)))))
219     (let ((block-tag (gensym))
220           (temp-var (gensym))
221           (data
222            (macrolet (;; KLUDGE: This started as an old DEFMACRO
223                       ;; WITH-KEYWORD-PAIRS general utility, which was used
224                       ;; only in this one place in the code. It was translated
225                       ;; literally into this MACROLET in order to avoid some
226                       ;; cross-compilation bootstrap problems. It would almost
227                       ;; certainly be clearer, and it would certainly be more
228                       ;; concise, to do a more idiomatic translation, merging
229                       ;; this with the TRANSFORM-KEYWORDS logic above.
230                       ;;   -- WHN 19990925
231                       (with-keyword-pairs ((names expression) &body forms)
232                         (let ((temp (member '&rest names)))
233                           (unless (= (length temp) 2)
234                             (error "&REST keyword is ~:[missing~;misplaced~]."
235                                    temp))
236                           (let* ((key-vars (ldiff names temp))
237                                  (keywords (mapcar #'keywordicate key-vars))
238                                  (key-var (gensym))
239                                  (rest-var (cadr temp)))
240                             `(multiple-value-bind (,key-var ,rest-var)
241                                  (parse-keyword-pairs ,expression ',keywords)
242                                (let ,(mapcar (lambda (var keyword)
243                                                `(,var (getf ,key-var
244                                                             ,keyword)))
245                                              key-vars keywords)
246                                  ,@forms))))))
247              (mapcar (lambda (clause)
248                        (with-keyword-pairs ((report interactive test
249                                                     &rest forms)
250                                             (cddr clause))
251                          (list (car clause) ;name=0
252                                (gensym) ;tag=1
253                                (transform-keywords :report report ;keywords=2
254                                                    :interactive interactive
255                                                    :test test)
256                                (cadr clause) ;bvl=3
257                                forms))) ;body=4
258                    clauses))))
259       `(block ,block-tag
260          (let ((,temp-var nil))
261            (tagbody
262             (restart-bind
263                 ,(mapcar (lambda (datum)
264                            (let ((name (nth 0 datum))
265                                  (tag  (nth 1 datum))
266                                  (keys (nth 2 datum)))
267                              `(,name #'(lambda (&rest temp)
268                                          (setq ,temp-var temp)
269                                          (go ,tag))
270                                      ,@keys)))
271                          data)
272               (return-from ,block-tag
273                            ,(munge-restart-case-expression expression data)))
274             ,@(mapcan (lambda (datum)
275                         (let ((tag  (nth 1 datum))
276                               (bvl  (nth 3 datum))
277                               (body (nth 4 datum)))
278                           (list tag
279                                 `(return-from ,block-tag
280                                    (apply (lambda ,bvl ,@body)
281                                           ,temp-var)))))
282                       data)))))))
283
284 (defmacro with-simple-restart ((restart-name format-string
285                                              &rest format-arguments)
286                                &body forms)
287   #!+sb-doc
288   "(WITH-SIMPLE-RESTART (restart-name format-string format-arguments)
289    body)
290    If restart-name is not invoked, then all values returned by forms are
291    returned. If control is transferred to this restart, it immediately
292    returns the values NIL and T."
293   `(restart-case
294        ;; If there's just one body form, then don't use PROGN. This allows
295        ;; RESTART-CASE to "see" calls to ERROR, etc.
296        ,(if (= (length forms) 1) (car forms) `(progn ,@forms))
297      (,restart-name ()
298         :report (lambda (stream)
299                   (format stream ,format-string ,@format-arguments))
300       (values nil t))))
301 \f
302 ;;;; HANDLER-BIND
303
304 (defvar *handler-clusters* nil)
305
306 (defmacro handler-bind (bindings &body forms)
307   #!+sb-doc
308   "(HANDLER-BIND ( {(type handler)}* )  body)
309    Executes body in a dynamic context where the given handler bindings are
310    in effect. Each handler must take the condition being signalled as an
311    argument. The bindings are searched first to last in the event of a
312    signalled condition."
313   (let ((member-if (member-if (lambda (x)
314                                 (not (proper-list-of-length-p x 2)))
315                               bindings)))
316     (when member-if
317       (error "ill-formed handler binding: ~S" (first member-if))))
318   `(let ((*handler-clusters*
319           (cons (list ,@(mapcar (lambda (x) `(cons ',(car x) ,(cadr x)))
320                                 bindings))
321                 *handler-clusters*)))
322      (multiple-value-prog1
323          (progn
324            ,@forms)
325        ;; Wait for any float exceptions.
326        #!+x86 (float-wait))))
327 \f
328 ;;;; HANDLER-CASE
329
330 (defmacro handler-case (form &rest cases)
331   "(HANDLER-CASE form
332    { (type ([var]) body) }* )
333    Execute FORM in a context with handlers established for the condition
334    types. A peculiar property allows type to be :NO-ERROR. If such a clause
335    occurs, and form returns normally, all its values are passed to this clause
336    as if by MULTIPLE-VALUE-CALL.  The :NO-ERROR clause accepts more than one
337    var specification."
338
339   ;; FIXME: Replacing CADR, CDDDR and friends with DESTRUCTURING-BIND
340   ;; and names for the subexpressions would make it easier to
341   ;; understand the code below.
342   (let ((no-error-clause (assoc ':no-error cases)))
343     (if no-error-clause
344         (let ((normal-return (make-symbol "normal-return"))
345               (error-return  (make-symbol "error-return")))
346           `(block ,error-return
347              (multiple-value-call (lambda ,@(cdr no-error-clause))
348                (block ,normal-return
349                  (return-from ,error-return
350                    (handler-case (return-from ,normal-return ,form)
351                      ,@(remove no-error-clause cases)))))))
352         (let ((tag (gensym))
353               (var (gensym))
354               (annotated-cases (mapcar (lambda (case) (cons (gensym) case))
355                                        cases)))
356           `(block ,tag
357              (let ((,var nil))
358                (declare (ignorable ,var))
359                (tagbody
360                 (handler-bind
361                     ,(mapcar (lambda (annotated-case)
362                                (list (cadr annotated-case)
363                                      `(lambda (temp)
364                                         ,(if (caddr annotated-case)
365                                              `(setq ,var temp)
366                                              '(declare (ignore temp)))
367                                         (go ,(car annotated-case)))))
368                              annotated-cases)
369                   (return-from ,tag
370                     #!-x86 ,form
371                     #!+x86 (multiple-value-prog1 ,form
372                              ;; Need to catch FP errors here!
373                              (float-wait))))
374                 ,@(mapcan
375                    (lambda (annotated-case)
376                      (list (car annotated-case)
377                            (let ((body (cdddr annotated-case)))
378                              `(return-from
379                                   ,tag
380                                 ,(cond ((caddr annotated-case)
381                                         `(let ((,(caaddr annotated-case)
382                                                 ,var))
383                                            ,@body))
384                                        ((not (cdr body))
385                                         (car body))
386                                        (t
387                                         `(progn ,@body)))))))
388                    annotated-cases))))))))
389 \f
390 ;;;; helper functions for restartable error handling which couldn't be
391 ;;;; defined 'til now 'cause they use the RESTART-CASE macro
392
393 (defun assert-error (assertion places datum &rest arguments)
394   (let ((cond (if datum
395                 (coerce-to-condition datum
396                                                     arguments
397                                                     'simple-error
398                                                     'error)
399                 (make-condition 'simple-error
400                                 :format-control "The assertion ~S failed."
401                                 :format-arguments (list assertion)))))
402     (restart-case
403         (error cond)
404       (continue ()
405                 :report (lambda (stream)
406                           (format stream "Retry assertion")
407                           (if places
408                               (format stream
409                                       " with new value~P for ~{~S~^, ~}."
410                                       (length places)
411                                       places)
412                               (format stream ".")))
413                 nil))))
414
415 ;;; READ-EVALUATED-FORM is used as the interactive method for restart cases
416 ;;; setup by the Common Lisp "casing" (e.g., CCASE and CTYPECASE) macros
417 ;;; and by CHECK-TYPE.
418 (defun read-evaluated-form ()
419   (format *query-io* "~&Type a form to be evaluated:~%")
420   (list (eval (read *query-io*))))
421
422 (defun check-type-error (place place-value type type-string)
423   (let ((cond (if type-string
424                   (make-condition 'simple-type-error
425                                   :datum place
426                                   :expected-type type
427                                   :format-control
428                                   "The value of ~S is ~S, which is not ~A."
429                                   :format-arguments (list place
430                                                           place-value
431                                                           type-string))
432                   (make-condition 'simple-type-error
433                                   :datum place
434                                   :expected-type type
435                                   :format-control
436                           "The value of ~S is ~S, which is not of type ~S."
437                                   :format-arguments (list place
438                                                           place-value
439                                                           type)))))
440     (restart-case (error cond)
441       (store-value (value)
442         :report (lambda (stream)
443                   (format stream "Supply a new value for ~S." place))
444         :interactive read-evaluated-form
445         value))))
446
447 (defun case-body-error (name keyform keyform-value expected-type keys)
448   (restart-case
449       (error 'case-failure
450              :name name
451              :datum keyform-value
452              :expected-type expected-type
453              :possibilities keys)
454     (store-value (value)
455       :report (lambda (stream)
456                 (format stream "Supply a new value for ~S." keyform))
457       :interactive read-evaluated-form
458       value)))