0.pre7.29:
[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 (defun compute-restarts (&optional condition)
25   #!+sb-doc
26   "Return a list of all the currently active restarts ordered from most
27    recently established to less recently established. If Condition is
28    specified, then only restarts associated with Condition (or with no
29    condition) will be returned."
30   (let ((associated ())
31         (other ()))
32     (dolist (alist *condition-restarts*)
33       (if (eq (car alist) condition)
34           (setq associated (cdr alist))
35           (setq other (append (cdr alist) other))))
36     (collect ((res))
37       (dolist (restart-cluster *restart-clusters*)
38         (dolist (restart restart-cluster)
39           (when (and (or (not condition)
40                          (member restart associated)
41                          (not (member restart other)))
42                      (funcall (restart-test-function restart) condition))
43             (res restart))))
44       (res))))
45
46 (defstruct (restart (:copier nil))
47   name
48   function
49   report-function
50   interactive-function
51   (test-function #'(lambda (cond) (declare (ignore cond)) t)))
52 (def!method print-object ((restart restart) stream)
53   (if *print-escape*
54       (print-unreadable-object (restart stream :type t :identity t))
55       (restart-report restart stream)))
56
57 #!+sb-doc
58 (setf (fdocumentation 'restart-name 'function)
59       "Returns the name of the given restart object.")
60
61 (defun restart-report (restart stream)
62   (funcall (or (restart-report-function restart)
63                (let ((name (restart-name restart)))
64                  #'(lambda (stream)
65                      (if name (format stream "~S" name)
66                               (format stream "~S" restart)))))
67            stream))
68
69 (defmacro with-condition-restarts (condition-form restarts-form &body body)
70   #!+sb-doc
71   "WITH-CONDITION-RESTARTS Condition-Form Restarts-Form Form*
72    Evaluates the Forms in a dynamic environment where the restarts in the list
73    Restarts-Form are associated with the condition returned by Condition-Form.
74    This allows FIND-RESTART, etc., to recognize restarts that are not related
75    to the error currently being debugged. See also RESTART-CASE."
76   (let ((n-cond (gensym)))
77     `(let ((*condition-restarts*
78             (cons (let ((,n-cond ,condition-form))
79                     (cons ,n-cond
80                           (append ,restarts-form
81                                   (cdr (assoc ,n-cond *condition-restarts*)))))
82                   *condition-restarts*)))
83        ,@body)))
84
85 (defmacro restart-bind (bindings &body forms)
86   #!+sb-doc
87   "Executes forms in a dynamic context where the given restart bindings are
88    in effect. Users probably want to use RESTART-CASE. When clauses contain
89    the same restart name, FIND-RESTART will find the first such clause."
90   `(let ((*restart-clusters*
91           (cons (list
92                  ,@(mapcar #'(lambda (binding)
93                                (unless (or (car binding)
94                                            (member :report-function
95                                                    binding
96                                                    :test #'eq))
97                                  (warn "Unnamed restart does not have a ~
98                                         report function: ~S"
99                                        binding))
100                                `(make-restart
101                                  :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   "Returns the first restart named name. If name is a restart, it is returned
111    if it is currently active. If no such restart is found, nil is returned.
112    It is an error to supply nil as a name. If Condition is specified and not
113    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   (let ((real-restart (find-restart restart)))
126     (unless real-restart
127       (error 'simple-control-error
128              :format-control "Restart ~S is not active."
129              :format-arguments (list restart)))
130     (apply (restart-function real-restart) values)))
131
132 (defun invoke-restart-interactively (restart)
133   #!+sb-doc
134   "Calls the function associated with the given restart, prompting for any
135    necessary arguments. If the argument restart is not a restart or a
136    currently active non-nil restart name, then a control-error is signalled."
137   (let ((real-restart (find-restart restart)))
138     (unless real-restart
139       (error 'simple-control-error
140              :format-control "Restart ~S is not active."
141              :format-arguments (list restart)))
142     (apply (restart-function real-restart)
143            (let ((interactive-function
144                   (restart-interactive-function real-restart)))
145              (if interactive-function
146                  (funcall interactive-function)
147                  '())))))
148
149 (eval-when (:compile-toplevel :load-toplevel :execute)
150 ;;; Wrap the RESTART-CASE expression in a WITH-CONDITION-RESTARTS if
151 ;;; appropriate. Gross, but it's what the book seems to say...
152 (defun munge-restart-case-expression (expression data)
153   (let ((exp (macroexpand expression)))
154     (if (consp exp)
155         (let* ((name (car exp))
156                (args (if (eq name 'cerror) (cddr exp) (cdr exp))))
157           (if (member name '(signal error cerror warn))
158               (once-only ((n-cond `(coerce-to-condition
159                                     ,(first args)
160                                     (list ,@(rest args))
161                                     ',(case name
162                                         (warn 'simple-warning)
163                                         (signal 'simple-condition)
164                                         (t 'simple-error))
165                                     ',name)))
166                 `(with-condition-restarts
167                      ,n-cond
168                      (list ,@(mapcar (lambda (da)
169                                        `(find-restart ',(nth 0 da)))
170                                      data))
171                    ,(if (eq name 'cerror)
172                         `(cerror ,(second expression) ,n-cond)
173                         `(,name ,n-cond))))
174               expression))
175         expression)))
176 ) ; EVAL-WHEN
177
178 ;;; FIXME: I did a fair amount of rearrangement of this code in order to
179 ;;; get WITH-KEYWORD-PAIRS to work cleanly. This code should be tested..
180 (defmacro restart-case (expression &body clauses)
181   #!+sb-doc
182   "(RESTART-CASE form
183    {(case-name arg-list {keyword value}* body)}*)
184    The form is evaluated in a dynamic context where the clauses have special
185    meanings as points to which control may be transferred (see INVOKE-RESTART).
186    When clauses contain the same case-name, FIND-RESTART will find the first
187    such clause. If Expression is a call to SIGNAL, ERROR, CERROR or WARN (or
188    macroexpands into such) then the signalled condition will be associated with
189    the new restarts."
190   (flet ((transform-keywords (&key report interactive test)
191            (let ((result '()))
192              (when report
193                (setq result (list* (if (stringp report)
194                                        `#'(lambda (stream)
195                                             (write-string ,report stream))
196                                        `#',report)
197                                    :report-function
198                                    result)))
199              (when interactive
200                (setq result (list* `#',interactive
201                                    :interactive-function
202                                    result)))
203              (when test
204                (setq result (list* `#',test
205                                    :test-function
206                                    result)))
207              (nreverse result)))
208          (parse-keyword-pairs (list keys)
209            (do ((l list (cddr l))
210                 (k '() (list* (cadr l) (car l) k)))
211                ((or (null l) (not (member (car l) keys)))
212                 (values (nreverse k) l)))))
213     (let ((block-tag (gensym))
214           (temp-var (gensym))
215           (data
216            (macrolet (;; KLUDGE: This started as an old DEFMACRO
217                       ;; WITH-KEYWORD-PAIRS general utility, which was used
218                       ;; only in this one place in the code. It was translated
219                       ;; literally into this MACROLET in order to avoid some
220                       ;; cross-compilation bootstrap problems. It would almost
221                       ;; certainly be clearer, and it would certainly be more
222                       ;; concise, to do a more idiomatic translation, merging
223                       ;; this with the TRANSFORM-KEYWORDS logic above.
224                       ;;   -- WHN 19990925
225                       (with-keyword-pairs ((names expression) &body forms)
226                         (let ((temp (member '&rest names)))
227                           (unless (= (length temp) 2)
228                             (error "&REST keyword is ~:[missing~;misplaced~]."
229                                    temp))
230                           (let* ((key-vars (ldiff names temp))
231                                  (keywords (mapcar #'keywordicate key-vars))
232                                  (key-var (gensym))
233                                  (rest-var (cadr temp)))
234                             `(multiple-value-bind (,key-var ,rest-var)
235                                  (parse-keyword-pairs ,expression ',keywords)
236                                (let ,(mapcar (lambda (var keyword)
237                                                `(,var (getf ,key-var
238                                                             ,keyword)))
239                                              key-vars keywords)
240                                  ,@forms))))))
241              (mapcar (lambda (clause)
242                        (with-keyword-pairs ((report interactive test
243                                                     &rest forms)
244                                             (cddr clause))
245                          (list (car clause) ;name=0
246                                (gensym) ;tag=1
247                                (transform-keywords :report report ;keywords=2
248                                                    :interactive interactive
249                                                    :test test)
250                                (cadr clause) ;bvl=3
251                                forms))) ;body=4
252                    clauses))))
253       `(block ,block-tag
254          (let ((,temp-var nil))
255            (tagbody
256             (restart-bind
257                 ,(mapcar #'(lambda (datum)
258                              (let ((name (nth 0 datum))
259                                    (tag  (nth 1 datum))
260                                    (keys (nth 2 datum)))
261                                `(,name #'(lambda (&rest temp)
262                                            (setq ,temp-var temp)
263                                            (go ,tag))
264                                        ,@keys)))
265                          data)
266               (return-from ,block-tag
267                            ,(munge-restart-case-expression expression data)))
268             ,@(mapcan #'(lambda (datum)
269                           (let ((tag  (nth 1 datum))
270                                 (bvl  (nth 3 datum))
271                                 (body (nth 4 datum)))
272                             (list tag
273                                   `(return-from ,block-tag
274                                                 (apply #'(lambda ,bvl ,@body)
275                                                        ,temp-var)))))
276                       data)))))))
277
278 (defmacro with-simple-restart ((restart-name format-string
279                                              &rest format-arguments)
280                                &body forms)
281   #!+sb-doc
282   "(WITH-SIMPLE-RESTART (restart-name format-string format-arguments)
283    body)
284    If restart-name is not invoked, then all values returned by forms are
285    returned. If control is transferred to this restart, it immediately
286    returns the values nil and t."
287   `(restart-case
288        ;; If there's just one body form, then don't use PROGN. This allows
289        ;; RESTART-CASE to "see" calls to ERROR, etc.
290        ,(if (= (length forms) 1) (car forms) `(progn ,@forms))
291      (,restart-name ()
292         :report (lambda (stream)
293                   (format stream ,format-string ,@format-arguments))
294       (values nil t))))
295 \f
296 ;;;; HANDLER-BIND
297
298 (defvar *handler-clusters* nil)
299
300 (defmacro handler-bind (bindings &body forms)
301   #!+sb-doc
302   "(HANDLER-BIND ( {(type handler)}* )  body)
303    Executes body in a dynamic context where the given handler bindings are
304    in effect. Each handler must take the condition being signalled as an
305    argument. The bindings are searched first to last in the event of a
306    signalled condition."
307   (let ((member-if (member-if (lambda (x)
308                                 (not (proper-list-of-length-p x 2)))
309                               bindings)))
310     (when member-if
311       (error "ill-formed handler binding: ~S" (first member-if))))
312   `(let ((*handler-clusters*
313           (cons (list ,@(mapcar #'(lambda (x) `(cons ',(car x) ,(cadr x)))
314                                 bindings))
315                 *handler-clusters*)))
316      (multiple-value-prog1
317          (progn
318            ,@forms)
319        ;; Wait for any float exceptions.
320        #!+x86 (float-wait))))
321 \f
322 ;;;; HANDLER-CASE
323
324 (defmacro handler-case (form &rest cases)
325   "(HANDLER-CASE form
326    { (type ([var]) body) }* )
327    Execute FORM in a context with handlers established for the condition
328    types. A peculiar property allows type to be :no-error. If such a clause
329    occurs, and form returns normally, all its values are passed to this clause
330    as if by MULTIPLE-VALUE-CALL.  The :NO-ERROR clause accepts more than one
331    var specification."
332
333   ;; FIXME: This old SBCL code uses multiple nested THROW/CATCH
334   ;; operations, which seems like an ugly way to handle lexical
335   ;; nonlocal exit. MNA sbcl-devel 2001-07-17 provided a patch
336   ;; (included below this form, but #+NIL'ed out) to switch over to
337   ;; RETURN-FROM, which seems like basically a better idea.
338   ;; Unfortunately when using his patch, this reasonable code
339   ;;    (DEFUN FOO1I ()
340   ;;      (IF (NOT (IGNORE-ERRORS
341   ;;                 (MAKE-PATHNAME :HOST "FOO"
342   ;;                                :DIRECTORY "!BLA"
343   ;;                                :NAME "BAR")))
344   ;;          (PRINT "OK")
345   ;;          (ERROR "NOTUNLESSNOT")))
346   ;; fails (doing ERROR "NOTUNLESSNOT" when it should PRINT "OK"
347   ;; instead). I think this may not be a bug in MNA's patch, but 
348   ;; instead in the rest of the compiler (e.g. handling of RETURN-FROM)
349   ;; but whatever the reason. (I noticed this problem in
350   ;; sbcl-0.pre7.14.flaky4.11, and reverted to the old code at that point.
351   ;; The problem also occurs at least in sbcl-0.6.12.59 and
352   ;; sbcl-0.6.13.) -- WHN
353   (let ((no-error-clause (assoc ':no-error cases)))
354     (if no-error-clause
355         (let ((normal-return (make-symbol "normal-return"))
356               (error-return  (make-symbol "error-return")))
357           `(block ,error-return
358              (multiple-value-call #'(lambda ,@(cdr no-error-clause))
359                (block ,normal-return
360                  (return-from ,error-return
361                    (handler-case (return-from ,normal-return ,form)
362                      ,@(remove no-error-clause cases)))))))
363         (let ((var (gensym))
364               (outer-tag (gensym))
365               (inner-tag (gensym))
366               (tag-var (gensym))
367               (annotated-cases (mapcar #'(lambda (case) (cons (gensym) case))
368                                        cases)))
369           `(let ((,outer-tag (cons nil nil))
370                  (,inner-tag (cons nil nil))
371                  ,var ,tag-var)
372              ;; FIXME: should be (DECLARE (IGNORABLE ,VAR))
373              ,var                       ;ignoreable
374              (catch ,outer-tag
375                (catch ,inner-tag
376                  (throw ,outer-tag
377                         (handler-bind
378                             ,(mapcar #'(lambda (annotated-case)
379                                          `(,(cadr annotated-case)
380                                            #'(lambda (temp)
381                                                ,(if (caddr annotated-case)
382                                                     `(setq ,var temp)
383                                                     '(declare (ignore temp)))
384                                                (setf ,tag-var
385                                                      ',(car annotated-case))
386                                                (throw ,inner-tag nil))))
387                                      annotated-cases)
388                           ,form)))
389                (case ,tag-var
390                  ,@(mapcar #'(lambda (annotated-case)
391                                (let ((body (cdddr annotated-case))
392                                      (varp (caddr annotated-case)))
393                                  `(,(car annotated-case)
394                                    ,@(if varp
395                                          `((let ((,(car varp) ,var))
396                                              ,@body))
397                                          body))))
398                            annotated-cases)))))))
399   #+nil ; MNA's patched version -- see FIXME above
400   (let ((no-error-clause (assoc ':no-error cases)))
401     (if no-error-clause
402         (let ((normal-return (make-symbol "normal-return"))
403               (error-return  (make-symbol "error-return")))
404           `(block ,error-return
405              (multiple-value-call (lambda ,@(cdr no-error-clause))
406                (block ,normal-return
407                  (return-from ,error-return
408                    (handler-case (return-from ,normal-return ,form)
409                      ,@(remove no-error-clause cases)))))))
410         (let ((tag (gensym))
411               (var (gensym))
412               (annotated-cases (mapcar (lambda (case) (cons (gensym) case))
413                                        cases)))
414           `(block ,tag
415              (let ((,var nil))
416                (declare (ignorable ,var))
417                (tagbody
418                 (handler-bind
419                     ,(mapcar (lambda (annotated-case)
420                                (list (cadr annotated-case)
421                                      `(lambda (temp)
422                                         ,(if (caddr annotated-case)
423                                              `(setq ,var temp)
424                                              '(declare (ignore temp)))
425                                         (go ,(car annotated-case)))))
426                              annotated-cases)
427                   (return-from ,tag
428                     #!-x86 ,form
429                     #!+x86 (multiple-value-prog1 ,form
430                              ;; Need to catch FP errors here!
431                              (float-wait))))
432                 ,@(mapcan
433                    (lambda (annotated-case)
434                      (list (car annotated-case)
435                            (let ((body (cdddr annotated-case)))
436                              `(return-from
437                                   ,tag
438                                 ,(cond ((caddr annotated-case)
439                                         `(let ((,(caaddr annotated-case)
440                                                 ,var))
441                                            ,@body))
442                                        ((not (cdr body))
443                                         (car body))
444                                        (t
445                                         `(progn ,@body)))))))
446                    annotated-cases))))))))
447 \f
448 ;;;; helper functions for restartable error handling which couldn't be
449 ;;;; defined 'til now 'cause they use the RESTART-CASE macro
450
451 (defun assert-error (assertion places datum &rest arguments)
452   (let ((cond (if datum
453                 (coerce-to-condition datum
454                                                     arguments
455                                                     'simple-error
456                                                     'error)
457                 (make-condition 'simple-error
458                                 :format-control "The assertion ~S failed."
459                                 :format-arguments (list assertion)))))
460     (restart-case
461         (error cond)
462       (continue ()
463                 :report (lambda (stream)
464                           (format stream "Retry assertion")
465                           (if places
466                               (format stream
467                                       " with new value~P for ~{~S~^, ~}."
468                                       (length places)
469                                       places)
470                               (format stream ".")))
471                 nil))))
472
473 ;;; READ-EVALUATED-FORM is used as the interactive method for restart cases
474 ;;; setup by the Common Lisp "casing" (e.g., CCASE and CTYPECASE) macros
475 ;;; and by CHECK-TYPE.
476 (defun read-evaluated-form ()
477   (format *query-io* "~&Type a form to be evaluated:~%")
478   (list (eval (read *query-io*))))
479
480 (defun check-type-error (place place-value type type-string)
481   (let ((cond (if type-string
482                   (make-condition 'simple-type-error
483                                   :datum place
484                                   :expected-type type
485                                   :format-control
486                                   "The value of ~S is ~S, which is not ~A."
487                                   :format-arguments (list place
488                                                           place-value
489                                                           type-string))
490                   (make-condition 'simple-type-error
491                                   :datum place
492                                   :expected-type type
493                                   :format-control
494                           "The value of ~S is ~S, which is not of type ~S."
495                                   :format-arguments (list place
496                                                           place-value
497                                                           type)))))
498     (restart-case (error cond)
499       (store-value (value)
500         :report (lambda (stream)
501                   (format stream "Supply a new value for ~S." place))
502         :interactive read-evaluated-form
503         value))))
504
505 (defun case-body-error (name keyform keyform-value expected-type keys)
506   (restart-case
507       (error 'case-failure
508              :name name
509              :datum keyform-value
510              :expected-type expected-type
511              :possibilities keys)
512     (store-value (value)
513       :report (lambda (stream)
514                 (format stream "Supply a new value for ~S." keyform))
515       :interactive read-evaluated-form
516       value)))