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